hasql/threads-test/Main.hs

45 lines
1.4 KiB
Haskell
Raw Normal View History

2016-03-06 13:44:56 +03:00
module Main where
import qualified Hasql.Connection
import qualified Hasql.Decoders
2022-06-20 13:54:54 +03:00
import qualified Hasql.Encoders
2016-03-06 13:44:56 +03:00
import qualified Hasql.Session
2022-06-20 13:54:54 +03:00
import qualified Hasql.Statement
2018-05-23 13:33:34 +03:00
import qualified Main.Statements as Statements
2022-06-20 13:54:54 +03:00
import Prelude
2016-03-06 13:44:56 +03:00
main =
acquire >>= use
where
acquire =
(,) <$> acquire <*> acquire
where
acquire =
2023-10-13 02:24:12 +03:00
join
$ fmap (either (fail . show) return)
$ Hasql.Connection.acquire connectionSettings
2016-03-06 13:44:56 +03:00
where
connectionSettings =
Hasql.Connection.settings "localhost" 5432 "postgres" "" "postgres"
use (connection1, connection2) =
do
beginVar <- newEmptyMVar
finishVar <- newEmptyMVar
forkIO $ do
traceM "1: in"
putMVar beginVar ()
2018-05-23 13:33:34 +03:00
session connection1 (Hasql.Session.statement 0.2 Statements.selectSleep)
2016-03-06 13:44:56 +03:00
traceM "1: out"
void (tryPutMVar finishVar False)
forkIO $ do
takeMVar beginVar
traceM "2: in"
2018-05-23 13:33:34 +03:00
session connection2 (Hasql.Session.statement 0.1 Statements.selectSleep)
2016-03-06 13:44:56 +03:00
traceM "2: out"
void (tryPutMVar finishVar True)
bool exitFailure exitSuccess . traceShowId =<< takeMVar finishVar
where
session connection session =
2022-06-20 13:54:54 +03:00
Hasql.Session.run session connection
>>= either (fail . show) return