module Hasql.Pool.Handle
(
Handle,
with,
Error(..),
session,
)
where
import Hasql.Pool.Prelude hiding (Handle)
import qualified Hasql.Pool
import qualified Hasql.Connection
import qualified Hasql.Session
newtype Handle s =
Handle (forall a. Hasql.Session.Session a -> IO (Either Error a))
with :: Int -> NominalDiffTime -> Hasql.Connection.Settings -> (forall s. Handle s -> IO a) -> IO a
with size timeout settings handler =
acquire >>= \pool -> use pool <* release pool
where
acquire =
Hasql.Pool.acquire size timeout settings
use pool =
handler $ Handle $ \session ->
fmap (either (Left . Left) (either (Left . Right) Right)) $
Hasql.Pool.use pool $
Hasql.Session.run session
release pool =
Hasql.Pool.release pool
type Error =
Either Hasql.Connection.ConnectionError Hasql.Session.Error
session :: Handle s -> Hasql.Session.Session a -> IO (Either Error a)
session (Handle runSession) session =
runSession session