hasql/library/Hasql/Session/Core.hs

68 lines
2.7 KiB
Haskell
Raw Normal View History

module Hasql.Session.Core where
2015-12-21 16:11:14 +03:00
2024-04-19 07:38:30 +03:00
import Hasql.Connection.Core qualified as Connection
import Hasql.Decoders.All qualified as Decoders
2024-04-19 07:38:30 +03:00
import Hasql.Decoders.Result qualified as Decoders.Result
import Hasql.Decoders.Results qualified as Decoders.Results
import Hasql.Encoders.All qualified as Encoders
import Hasql.Encoders.Params qualified as Encoders.Params
import Hasql.Errors
2024-04-19 07:38:30 +03:00
import Hasql.IO qualified as IO
import Hasql.Pipeline.Core qualified as Pipeline
import Hasql.Prelude
2024-04-19 07:38:30 +03:00
import Hasql.Statement qualified as Statement
2015-12-21 16:11:14 +03:00
-- |
-- A batch of actions to be executed in the context of a database connection.
2022-06-20 13:54:54 +03:00
newtype Session a
= Session (ReaderT Connection.Connection (ExceptT SessionError IO) a)
deriving (Functor, Applicative, Monad, MonadError SessionError, MonadIO, MonadReader Connection.Connection)
2015-12-21 16:45:10 +03:00
-- |
-- Executes a bunch of commands on the provided connection.
run :: Session a -> Connection.Connection -> IO (Either SessionError a)
2015-12-21 16:45:10 +03:00
run (Session impl) connection =
2023-10-13 02:24:12 +03:00
runExceptT
$ runReaderT impl connection
2015-12-21 16:11:14 +03:00
-- |
-- Possibly a multi-statement query,
-- which however cannot be parameterized or prepared,
-- nor can any results of it be collected.
sql :: ByteString -> Session ()
sql sql =
2023-10-13 02:24:12 +03:00
Session
$ ReaderT
$ \(Connection.Connection pqConnectionRef integerDatetimes registry) ->
ExceptT
$ fmap (mapLeft (QuerySessionError sql []))
2023-10-13 02:24:12 +03:00
$ withMVar pqConnectionRef
$ \pqConnection -> do
r1 <- IO.sendNonparametricStatement pqConnection sql
r2 <- IO.getResults pqConnection integerDatetimes decoder
return $ r1 *> r2
2016-01-22 18:50:13 +03:00
where
decoder =
2019-05-21 13:25:22 +03:00
Decoders.Results.single Decoders.Result.noResult
2015-12-21 16:11:14 +03:00
-- |
2018-05-23 13:33:34 +03:00
-- Parameters and a specification of a parametric single-statement query to apply them to.
statement :: params -> Statement.Statement params result -> Session result
statement input (Statement.Statement template (Encoders.Params paramsEncoder) (Decoders.Result decoder) preparable) =
2023-10-13 02:24:12 +03:00
Session
$ ReaderT
$ \(Connection.Connection pqConnectionRef integerDatetimes registry) ->
ExceptT
$ fmap (mapLeft (QuerySessionError template (Encoders.Params.renderReadable paramsEncoder input)))
2023-10-13 02:24:12 +03:00
$ withMVar pqConnectionRef
$ \pqConnection -> do
r1 <- IO.sendParametricStatement pqConnection integerDatetimes registry template paramsEncoder preparable input
r2 <- IO.getResults pqConnection integerDatetimes decoder
2023-10-13 02:24:12 +03:00
return $ r1 *> r2
pipeline :: Pipeline.Pipeline result -> Session result
pipeline pipeline =
2024-04-22 07:02:26 +03:00
Session $ ReaderT \(Connection.Connection pqConnectionRef integerDatetimes registry) ->
ExceptT $ withMVar pqConnectionRef \pqConnection ->
Pipeline.run pipeline pqConnection registry integerDatetimes