module Hasql.Private.Session
where

import Hasql.Private.Prelude
import Hasql.Private.Errors
import qualified Database.PostgreSQL.LibPQ as LibPQ
import qualified Hasql.Private.Decoders.Results as Decoders.Results
import qualified Hasql.Private.Decoders.Result as Decoders.Result
import qualified Hasql.Private.Encoders.Params as Encoders.Params
import qualified Hasql.Private.Encoders as Encoders
import qualified Hasql.Private.Settings as Settings
import qualified Hasql.Private.IO as IO
import qualified Hasql.Statement as Statement
import qualified Hasql.Private.Connection as Connection


-- |
-- A batch of actions to be executed in the context of a database connection.
newtype Session a =
  Session (ReaderT Connection.Connection (ExceptT QueryError IO) a)
  deriving (a -> Session b -> Session a
(a -> b) -> Session a -> Session b
(forall a b. (a -> b) -> Session a -> Session b)
-> (forall a b. a -> Session b -> Session a) -> Functor Session
forall a b. a -> Session b -> Session a
forall a b. (a -> b) -> Session a -> Session b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Session b -> Session a
$c<$ :: forall a b. a -> Session b -> Session a
fmap :: (a -> b) -> Session a -> Session b
$cfmap :: forall a b. (a -> b) -> Session a -> Session b
Functor, Functor Session
a -> Session a
Functor Session
-> (forall a. a -> Session a)
-> (forall a b. Session (a -> b) -> Session a -> Session b)
-> (forall a b c.
    (a -> b -> c) -> Session a -> Session b -> Session c)
-> (forall a b. Session a -> Session b -> Session b)
-> (forall a b. Session a -> Session b -> Session a)
-> Applicative Session
Session a -> Session b -> Session b
Session a -> Session b -> Session a
Session (a -> b) -> Session a -> Session b
(a -> b -> c) -> Session a -> Session b -> Session c
forall a. a -> Session a
forall a b. Session a -> Session b -> Session a
forall a b. Session a -> Session b -> Session b
forall a b. Session (a -> b) -> Session a -> Session b
forall a b c. (a -> b -> c) -> Session a -> Session b -> Session c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: Session a -> Session b -> Session a
$c<* :: forall a b. Session a -> Session b -> Session a
*> :: Session a -> Session b -> Session b
$c*> :: forall a b. Session a -> Session b -> Session b
liftA2 :: (a -> b -> c) -> Session a -> Session b -> Session c
$cliftA2 :: forall a b c. (a -> b -> c) -> Session a -> Session b -> Session c
<*> :: Session (a -> b) -> Session a -> Session b
$c<*> :: forall a b. Session (a -> b) -> Session a -> Session b
pure :: a -> Session a
$cpure :: forall a. a -> Session a
$cp1Applicative :: Functor Session
Applicative, Applicative Session
a -> Session a
Applicative Session
-> (forall a b. Session a -> (a -> Session b) -> Session b)
-> (forall a b. Session a -> Session b -> Session b)
-> (forall a. a -> Session a)
-> Monad Session
Session a -> (a -> Session b) -> Session b
Session a -> Session b -> Session b
forall a. a -> Session a
forall a b. Session a -> Session b -> Session b
forall a b. Session a -> (a -> Session b) -> Session b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Session a
$creturn :: forall a. a -> Session a
>> :: Session a -> Session b -> Session b
$c>> :: forall a b. Session a -> Session b -> Session b
>>= :: Session a -> (a -> Session b) -> Session b
$c>>= :: forall a b. Session a -> (a -> Session b) -> Session b
$cp1Monad :: Applicative Session
Monad, MonadError QueryError, Monad Session
Monad Session -> (forall a. IO a -> Session a) -> MonadIO Session
IO a -> Session a
forall a. IO a -> Session a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> Session a
$cliftIO :: forall a. IO a -> Session a
$cp1MonadIO :: Monad Session
MonadIO, MonadReader Connection.Connection)

-- |
-- Executes a bunch of commands on the provided connection.
run :: Session a -> Connection.Connection -> IO (Either QueryError a)
run :: Session a -> Connection -> IO (Either QueryError a)
run (Session ReaderT Connection (ExceptT QueryError IO) a
impl) Connection
connection =
  ExceptT QueryError IO a -> IO (Either QueryError a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT QueryError IO a -> IO (Either QueryError a))
-> ExceptT QueryError IO a -> IO (Either QueryError a)
forall a b. (a -> b) -> a -> b
$
  ReaderT Connection (ExceptT QueryError IO) a
-> Connection -> ExceptT QueryError IO a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT Connection (ExceptT QueryError IO) a
impl Connection
connection

-- |
-- Possibly a multi-statement query,
-- which however cannot be parameterized or prepared,
-- nor can any results of it be collected.
sql :: ByteString -> Session ()
sql :: ByteString -> Session ()
sql ByteString
sql =
  ReaderT Connection (ExceptT QueryError IO) () -> Session ()
forall a. ReaderT Connection (ExceptT QueryError IO) a -> Session a
Session (ReaderT Connection (ExceptT QueryError IO) () -> Session ())
-> ReaderT Connection (ExceptT QueryError IO) () -> Session ()
forall a b. (a -> b) -> a -> b
$ (Connection -> ExceptT QueryError IO ())
-> ReaderT Connection (ExceptT QueryError IO) ()
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((Connection -> ExceptT QueryError IO ())
 -> ReaderT Connection (ExceptT QueryError IO) ())
-> (Connection -> ExceptT QueryError IO ())
-> ReaderT Connection (ExceptT QueryError IO) ()
forall a b. (a -> b) -> a -> b
$ \(Connection.Connection MVar Connection
pqConnectionRef Bool
integerDatetimes PreparedStatementRegistry
registry) ->
    IO (Either QueryError ()) -> ExceptT QueryError IO ()
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (IO (Either QueryError ()) -> ExceptT QueryError IO ())
-> IO (Either QueryError ()) -> ExceptT QueryError IO ()
forall a b. (a -> b) -> a -> b
$ (Either CommandError () -> Either QueryError ())
-> IO (Either CommandError ()) -> IO (Either QueryError ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CommandError -> QueryError)
-> Either CommandError () -> Either QueryError ()
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft (ByteString -> [Text] -> CommandError -> QueryError
QueryError ByteString
sql [])) (IO (Either CommandError ()) -> IO (Either QueryError ()))
-> IO (Either CommandError ()) -> IO (Either QueryError ())
forall a b. (a -> b) -> a -> b
$ MVar Connection
-> (Connection -> IO (Either CommandError ()))
-> IO (Either CommandError ())
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar Connection
pqConnectionRef ((Connection -> IO (Either CommandError ()))
 -> IO (Either CommandError ()))
-> (Connection -> IO (Either CommandError ()))
-> IO (Either CommandError ())
forall a b. (a -> b) -> a -> b
$ \Connection
pqConnection -> do
      Either CommandError ()
r1 <- Connection -> ByteString -> IO (Either CommandError ())
IO.sendNonparametricStatement Connection
pqConnection ByteString
sql
      Either CommandError ()
r2 <- Connection -> Bool -> Results () -> IO (Either CommandError ())
forall a.
Connection -> Bool -> Results a -> IO (Either CommandError a)
IO.getResults Connection
pqConnection Bool
integerDatetimes Results ()
decoder
      Either CommandError () -> IO (Either CommandError ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either CommandError () -> IO (Either CommandError ()))
-> Either CommandError () -> IO (Either CommandError ())
forall a b. (a -> b) -> a -> b
$ Either CommandError ()
r1 Either CommandError ()
-> Either CommandError () -> Either CommandError ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Either CommandError ()
r2
  where
    decoder :: Results ()
decoder =
      Result () -> Results ()
forall a. Result a -> Results a
Decoders.Results.single Result ()
Decoders.Result.noResult

-- |
-- Parameters and a specification of a parametric single-statement query to apply them to.
statement :: params -> Statement.Statement params result -> Session result
statement :: params -> Statement params result -> Session result
statement params
input (Statement.Statement ByteString
template (Encoders.Params Params params
paramsEncoder) Result result
decoder Bool
preparable) =
  ReaderT Connection (ExceptT QueryError IO) result -> Session result
forall a. ReaderT Connection (ExceptT QueryError IO) a -> Session a
Session (ReaderT Connection (ExceptT QueryError IO) result
 -> Session result)
-> ReaderT Connection (ExceptT QueryError IO) result
-> Session result
forall a b. (a -> b) -> a -> b
$ (Connection -> ExceptT QueryError IO result)
-> ReaderT Connection (ExceptT QueryError IO) result
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((Connection -> ExceptT QueryError IO result)
 -> ReaderT Connection (ExceptT QueryError IO) result)
-> (Connection -> ExceptT QueryError IO result)
-> ReaderT Connection (ExceptT QueryError IO) result
forall a b. (a -> b) -> a -> b
$ \(Connection.Connection MVar Connection
pqConnectionRef Bool
integerDatetimes PreparedStatementRegistry
registry) ->
    IO (Either QueryError result) -> ExceptT QueryError IO result
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (IO (Either QueryError result) -> ExceptT QueryError IO result)
-> IO (Either QueryError result) -> ExceptT QueryError IO result
forall a b. (a -> b) -> a -> b
$ (Either CommandError result -> Either QueryError result)
-> IO (Either CommandError result) -> IO (Either QueryError result)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CommandError -> QueryError)
-> Either CommandError result -> Either QueryError result
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft (ByteString -> [Text] -> CommandError -> QueryError
QueryError ByteString
template [Text]
inputReps)) (IO (Either CommandError result) -> IO (Either QueryError result))
-> IO (Either CommandError result) -> IO (Either QueryError result)
forall a b. (a -> b) -> a -> b
$ MVar Connection
-> (Connection -> IO (Either CommandError result))
-> IO (Either CommandError result)
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar Connection
pqConnectionRef ((Connection -> IO (Either CommandError result))
 -> IO (Either CommandError result))
-> (Connection -> IO (Either CommandError result))
-> IO (Either CommandError result)
forall a b. (a -> b) -> a -> b
$ \Connection
pqConnection -> do
      Either CommandError ()
r1 <- Connection
-> Bool
-> PreparedStatementRegistry
-> ByteString
-> Params params
-> Bool
-> params
-> IO (Either CommandError ())
forall a.
Connection
-> Bool
-> PreparedStatementRegistry
-> ByteString
-> Params a
-> Bool
-> a
-> IO (Either CommandError ())
IO.sendParametricStatement Connection
pqConnection Bool
integerDatetimes PreparedStatementRegistry
registry ByteString
template Params params
paramsEncoder Bool
preparable params
input
      Either CommandError result
r2 <- Connection
-> Bool -> Results result -> IO (Either CommandError result)
forall a.
Connection -> Bool -> Results a -> IO (Either CommandError a)
IO.getResults Connection
pqConnection Bool
integerDatetimes (Result result -> Results result
forall a b. a -> b
unsafeCoerce Result result
decoder)
      Either CommandError result -> IO (Either CommandError result)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either CommandError result -> IO (Either CommandError result))
-> Either CommandError result -> IO (Either CommandError result)
forall a b. (a -> b) -> a -> b
$ Either CommandError ()
r1 Either CommandError ()
-> Either CommandError result -> Either CommandError result
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Either CommandError result
r2
  where
    inputReps :: [Text]
inputReps =
      let
        Encoders.Params.Params (Op params -> DList (Oid, Format, Bool -> Maybe ByteString, Text)
encoderOp) = Params params
paramsEncoder
        step :: (a, b, c, a) -> [a] -> [a]
step (a
_, b
_, c
_, a
rendering) [a]
acc =
          a
rendering a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
acc
        in ((Oid, Format, Bool -> Maybe ByteString, Text) -> [Text] -> [Text])
-> [Text]
-> DList (Oid, Format, Bool -> Maybe ByteString, Text)
-> [Text]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Oid, Format, Bool -> Maybe ByteString, Text) -> [Text] -> [Text]
forall a b c a. (a, b, c, a) -> [a] -> [a]
step [] (params -> DList (Oid, Format, Bool -> Maybe ByteString, Text)
encoderOp params
input)