module Hasql.Pipeline.Core where
import Hasql.Decoders.All qualified as Decoders
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
import Hasql.LibPq14 qualified as Pq
import Hasql.Prelude
import Hasql.PreparedStatementRegistry qualified as PreparedStatementRegistry
import Hasql.Statement qualified as Statement
run :: forall a. Pipeline a -> Pq.Connection -> PreparedStatementRegistry.PreparedStatementRegistry -> Bool -> IO (Either SessionError a)
run :: forall a.
Pipeline a
-> Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError a)
run (Pipeline Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a)))
sendQueriesInIO) Connection
connection PreparedStatementRegistry
registry Bool
integerDatetimes = do
ExceptT SessionError IO a -> IO (Either SessionError a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT do
ExceptT SessionError IO ()
enterPipelineMode
ExceptT SessionError IO a
recvQueries <- ExceptT SessionError IO (ExceptT SessionError IO a)
sendQueries
ExceptT SessionError IO ()
pipelineSync
ExceptT SessionError IO a
-> ExceptT SessionError IO () -> ExceptT SessionError IO a
forall (m :: * -> *) e a.
Monad m =>
ExceptT e m a -> ExceptT e m () -> ExceptT e m a
finallyE ExceptT SessionError IO a
recvQueries do
ExceptT SessionError IO ()
recvPipelineSync
ExceptT SessionError IO ()
exitPipelineMode
where
enterPipelineMode :: ExceptT SessionError IO ()
enterPipelineMode :: ExceptT SessionError IO ()
enterPipelineMode =
IO Bool -> ExceptT SessionError IO ()
runCommand (IO Bool -> ExceptT SessionError IO ())
-> IO Bool -> ExceptT SessionError IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> IO Bool
Pq.enterPipelineMode Connection
connection
exitPipelineMode :: ExceptT SessionError IO ()
exitPipelineMode :: ExceptT SessionError IO ()
exitPipelineMode =
IO Bool -> ExceptT SessionError IO ()
runCommand (IO Bool -> ExceptT SessionError IO ())
-> IO Bool -> ExceptT SessionError IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> IO Bool
Pq.exitPipelineMode Connection
connection
sendQueries :: ExceptT SessionError IO (ExceptT SessionError IO a)
sendQueries :: ExceptT SessionError IO (ExceptT SessionError IO a)
sendQueries =
(IO (Either SessionError a) -> ExceptT SessionError IO a)
-> ExceptT SessionError IO (IO (Either SessionError a))
-> ExceptT SessionError IO (ExceptT SessionError IO a)
forall a b.
(a -> b) -> ExceptT SessionError IO a -> ExceptT SessionError IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IO (Either SessionError a) -> ExceptT SessionError IO a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (ExceptT SessionError IO (IO (Either SessionError a))
-> ExceptT SessionError IO (ExceptT SessionError IO a))
-> ExceptT SessionError IO (IO (Either SessionError a))
-> ExceptT SessionError IO (ExceptT SessionError IO a)
forall a b. (a -> b) -> a -> b
$ IO (Either SessionError (IO (Either SessionError a)))
-> ExceptT SessionError IO (IO (Either SessionError a))
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (IO (Either SessionError (IO (Either SessionError a)))
-> ExceptT SessionError IO (IO (Either SessionError a)))
-> IO (Either SessionError (IO (Either SessionError a)))
-> ExceptT SessionError IO (IO (Either SessionError a))
forall a b. (a -> b) -> a -> b
$ Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a)))
sendQueriesInIO Connection
connection PreparedStatementRegistry
registry Bool
integerDatetimes
pipelineSync :: ExceptT SessionError IO ()
pipelineSync :: ExceptT SessionError IO ()
pipelineSync =
IO Bool -> ExceptT SessionError IO ()
runCommand (IO Bool -> ExceptT SessionError IO ())
-> IO Bool -> ExceptT SessionError IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> IO Bool
Pq.pipelineSync Connection
connection
recvPipelineSync :: ExceptT SessionError IO ()
recvPipelineSync :: ExceptT SessionError IO ()
recvPipelineSync =
Results () -> ExceptT SessionError IO ()
forall a. Results a -> ExceptT SessionError IO a
runResultsDecoder
(Results () -> ExceptT SessionError IO ())
-> Results () -> ExceptT SessionError IO ()
forall a b. (a -> b) -> a -> b
$ Result () -> Results ()
forall a. Result a -> Results a
Decoders.Results.single Result ()
Decoders.Result.pipelineSync
runResultsDecoder :: forall a. Decoders.Results.Results a -> ExceptT SessionError IO a
runResultsDecoder :: forall a. Results a -> ExceptT SessionError IO a
runResultsDecoder Results a
decoder =
IO (Either SessionError a) -> ExceptT SessionError IO a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT
(IO (Either SessionError a) -> ExceptT SessionError IO a)
-> IO (Either SessionError a) -> ExceptT SessionError IO a
forall a b. (a -> b) -> a -> b
$ (Either CommandError a -> Either SessionError a)
-> IO (Either CommandError a) -> IO (Either SessionError a)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CommandError -> SessionError)
-> Either CommandError a -> Either SessionError a
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first CommandError -> SessionError
PipelineError)
(IO (Either CommandError a) -> IO (Either SessionError a))
-> IO (Either CommandError a) -> IO (Either SessionError a)
forall a b. (a -> b) -> a -> b
$ Results a -> Connection -> Bool -> IO (Either CommandError a)
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run Results a
decoder Connection
connection Bool
integerDatetimes
runCommand :: IO Bool -> ExceptT SessionError IO ()
runCommand :: IO Bool -> ExceptT SessionError IO ()
runCommand IO Bool
action =
IO Bool -> ExceptT SessionError IO Bool
forall (m :: * -> *) a. Monad m => m a -> ExceptT SessionError m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift IO Bool
action ExceptT SessionError IO Bool
-> (Bool -> ExceptT SessionError IO ())
-> ExceptT SessionError IO ()
forall a b.
ExceptT SessionError IO a
-> (a -> ExceptT SessionError IO b) -> ExceptT SessionError IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> () -> ExceptT SessionError IO ()
forall a. a -> ExceptT SessionError IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Bool
False -> IO (Either SessionError ()) -> ExceptT SessionError IO ()
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (SessionError -> Either SessionError ()
forall a b. a -> Either a b
Left (SessionError -> Either SessionError ())
-> (Maybe ByteString -> SessionError)
-> Maybe ByteString
-> Either SessionError ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CommandError -> SessionError
PipelineError (CommandError -> SessionError)
-> (Maybe ByteString -> CommandError)
-> Maybe ByteString
-> SessionError
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Maybe ByteString -> CommandError
ClientError (Maybe ByteString -> Either SessionError ())
-> IO (Maybe ByteString) -> IO (Either SessionError ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO (Maybe ByteString)
Pq.errorMessage Connection
connection)
newtype Pipeline a
= Pipeline
( Pq.Connection ->
PreparedStatementRegistry.PreparedStatementRegistry ->
Bool ->
IO (Either SessionError (IO (Either SessionError a)))
)
deriving ((forall a b. (a -> b) -> Pipeline a -> Pipeline b)
-> (forall a b. a -> Pipeline b -> Pipeline a) -> Functor Pipeline
forall a b. a -> Pipeline b -> Pipeline a
forall a b. (a -> b) -> Pipeline a -> Pipeline b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Pipeline a -> Pipeline b
fmap :: forall a b. (a -> b) -> Pipeline a -> Pipeline b
$c<$ :: forall a b. a -> Pipeline b -> Pipeline a
<$ :: forall a b. a -> Pipeline b -> Pipeline a
Functor)
instance Applicative Pipeline where
pure :: forall a. a -> Pipeline a
pure a
a =
(Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a))))
-> Pipeline a
forall a.
(Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a))))
-> Pipeline a
Pipeline (\Connection
_ PreparedStatementRegistry
_ Bool
_ -> Either SessionError (IO (Either SessionError a))
-> IO (Either SessionError (IO (Either SessionError a)))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO (Either SessionError a)
-> Either SessionError (IO (Either SessionError a))
forall a b. b -> Either a b
Right (Either SessionError a -> IO (Either SessionError a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either SessionError a
forall a b. b -> Either a b
Right a
a))))
Pipeline Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError (a -> b))))
lSend <*> :: forall a b. Pipeline (a -> b) -> Pipeline a -> Pipeline b
<*> Pipeline Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a)))
rSend =
(Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError b))))
-> Pipeline b
forall a.
(Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a))))
-> Pipeline a
Pipeline \Connection
conn PreparedStatementRegistry
reg Bool
integerDatetimes ->
Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError (a -> b))))
lSend Connection
conn PreparedStatementRegistry
reg Bool
integerDatetimes IO (Either SessionError (IO (Either SessionError (a -> b))))
-> (Either SessionError (IO (Either SessionError (a -> b)))
-> IO (Either SessionError (IO (Either SessionError b))))
-> IO (Either SessionError (IO (Either SessionError b)))
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left SessionError
sendErr ->
Either SessionError (IO (Either SessionError b))
-> IO (Either SessionError (IO (Either SessionError b)))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SessionError -> Either SessionError (IO (Either SessionError b))
forall a b. a -> Either a b
Left SessionError
sendErr)
Right IO (Either SessionError (a -> b))
lRecv ->
Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a)))
rSend Connection
conn PreparedStatementRegistry
reg Bool
integerDatetimes IO (Either SessionError (IO (Either SessionError a)))
-> (Either SessionError (IO (Either SessionError a))
-> Either SessionError (IO (Either SessionError b)))
-> IO (Either SessionError (IO (Either SessionError b)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
Left SessionError
sendErr ->
SessionError -> Either SessionError (IO (Either SessionError b))
forall a b. a -> Either a b
Left SessionError
sendErr
Right IO (Either SessionError a)
rRecv ->
IO (Either SessionError b)
-> Either SessionError (IO (Either SessionError b))
forall a b. b -> Either a b
Right ((Either SessionError (a -> b)
-> Either SessionError a -> Either SessionError b)
-> IO (Either SessionError (a -> b))
-> IO (Either SessionError a)
-> IO (Either SessionError b)
forall a b c. (a -> b -> c) -> IO a -> IO b -> IO c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Either SessionError (a -> b)
-> Either SessionError a -> Either SessionError b
forall a b.
Either SessionError (a -> b)
-> Either SessionError a -> Either SessionError b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>) IO (Either SessionError (a -> b))
lRecv IO (Either SessionError a)
rRecv)
statement :: params -> Statement.Statement params result -> Pipeline result
statement :: forall params result.
params -> Statement params result -> Pipeline result
statement params
params (Statement.Statement ByteString
sql (Encoders.Params Params params
encoder) (Decoders.Result Results result
decoder) Bool
preparable) =
(Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError result))))
-> Pipeline result
forall a.
(Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError a))))
-> Pipeline a
Pipeline Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError result)))
run
where
run :: Connection
-> PreparedStatementRegistry
-> Bool
-> IO (Either SessionError (IO (Either SessionError result)))
run Connection
connection PreparedStatementRegistry
registry Bool
integerDatetimes =
if Bool
preparable
then IO (Either SessionError (IO (Either SessionError result)))
runPrepared
else IO (Either SessionError (IO (Either SessionError result)))
runUnprepared
where
runPrepared :: IO (Either SessionError (IO (Either SessionError result)))
runPrepared = ExceptT SessionError IO (IO (Either SessionError result))
-> IO (Either SessionError (IO (Either SessionError result)))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT do
(ByteString
key, IO (Either SessionError ())
keyRecv) <- IO (Either SessionError (ByteString, IO (Either SessionError ())))
-> ExceptT
SessionError IO (ByteString, IO (Either SessionError ()))
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT IO (Either SessionError (ByteString, IO (Either SessionError ())))
resolvePreparedStatementKey
IO (Either SessionError result)
queryRecv <- IO (Either SessionError (IO (Either SessionError result)))
-> ExceptT SessionError IO (IO (Either SessionError result))
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (ByteString
-> IO (Either SessionError (IO (Either SessionError result)))
sendQuery ByteString
key)
pure (IO (Either SessionError ())
keyRecv IO (Either SessionError ())
-> IO (Either SessionError result)
-> IO (Either SessionError result)
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> IO (Either SessionError result)
queryRecv)
where
([Oid]
oidList, [Maybe (ByteString, Format)]
valueAndFormatList) =
Params params
-> Bool -> params -> ([Oid], [Maybe (ByteString, Format)])
forall a.
Params a -> Bool -> a -> ([Oid], [Maybe (ByteString, Format)])
Encoders.Params.compilePreparedStatementData Params params
encoder Bool
integerDatetimes params
params
resolvePreparedStatementKey :: IO (Either SessionError (ByteString, IO (Either SessionError ())))
resolvePreparedStatementKey =
LocalKey
-> (ByteString
-> IO
(Bool,
Either SessionError (ByteString, IO (Either SessionError ()))))
-> (ByteString
-> IO
(Either SessionError (ByteString, IO (Either SessionError ()))))
-> PreparedStatementRegistry
-> IO
(Either SessionError (ByteString, IO (Either SessionError ())))
forall a.
LocalKey
-> (ByteString -> IO (Bool, a))
-> (ByteString -> IO a)
-> PreparedStatementRegistry
-> IO a
PreparedStatementRegistry.update LocalKey
localKey ByteString
-> IO
(Bool,
Either SessionError (ByteString, IO (Either SessionError ())))
onNewRemoteKey ByteString
-> IO
(Either SessionError (ByteString, IO (Either SessionError ())))
forall {f :: * -> *} {f :: * -> *} {a} {a} {a}.
(Applicative f, Applicative f) =>
a -> f (Either a (a, f (Either a ())))
onOldRemoteKey PreparedStatementRegistry
registry
where
localKey :: LocalKey
localKey =
ByteString -> [Oid] -> LocalKey
PreparedStatementRegistry.LocalKey ByteString
sql [Oid]
oidList
onNewRemoteKey :: ByteString
-> IO
(Bool,
Either SessionError (ByteString, IO (Either SessionError ())))
onNewRemoteKey ByteString
key =
do
Bool
sent <- Connection -> ByteString -> ByteString -> Maybe [Oid] -> IO Bool
Pq.sendPrepare Connection
connection ByteString
key ByteString
sql (([Oid] -> Bool) -> Maybe [Oid] -> Maybe [Oid]
forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Bool -> Bool
not (Bool -> Bool) -> ([Oid] -> Bool) -> [Oid] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. [Oid] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([Oid] -> Maybe [Oid]
forall a. a -> Maybe a
Just [Oid]
oidList))
if Bool
sent
then (Bool,
Either SessionError (ByteString, IO (Either SessionError ())))
-> IO
(Bool,
Either SessionError (ByteString, IO (Either SessionError ())))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool
True, (ByteString, IO (Either SessionError ()))
-> Either SessionError (ByteString, IO (Either SessionError ()))
forall a b. b -> Either a b
Right (ByteString
key, IO (Either SessionError ())
recv))
else (Bool
False,) (Either SessionError (ByteString, IO (Either SessionError ()))
-> (Bool,
Either SessionError (ByteString, IO (Either SessionError ()))))
-> (Maybe ByteString
-> Either SessionError (ByteString, IO (Either SessionError ())))
-> Maybe ByteString
-> (Bool,
Either SessionError (ByteString, IO (Either SessionError ())))
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SessionError
-> Either SessionError (ByteString, IO (Either SessionError ()))
forall a b. a -> Either a b
Left (SessionError
-> Either SessionError (ByteString, IO (Either SessionError ())))
-> (Maybe ByteString -> SessionError)
-> Maybe ByteString
-> Either SessionError (ByteString, IO (Either SessionError ()))
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CommandError -> SessionError
commandToSessionError (CommandError -> SessionError)
-> (Maybe ByteString -> CommandError)
-> Maybe ByteString
-> SessionError
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Maybe ByteString -> CommandError
ClientError (Maybe ByteString
-> (Bool,
Either SessionError (ByteString, IO (Either SessionError ()))))
-> IO (Maybe ByteString)
-> IO
(Bool,
Either SessionError (ByteString, IO (Either SessionError ())))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO (Maybe ByteString)
Pq.errorMessage Connection
connection
where
recv :: IO (Either SessionError ())
recv =
(Either CommandError () -> Either SessionError ())
-> IO (Either CommandError ()) -> IO (Either SessionError ())
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CommandError -> SessionError)
-> Either CommandError () -> Either SessionError ()
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first CommandError -> SessionError
commandToSessionError)
(IO (Either CommandError ()) -> IO (Either SessionError ()))
-> IO (Either CommandError ()) -> IO (Either SessionError ())
forall a b. (a -> b) -> a -> b
$ Either CommandError ()
-> Either CommandError () -> Either CommandError ()
forall a b.
Either CommandError a
-> Either CommandError b -> Either CommandError a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
(<*)
(Either CommandError ()
-> Either CommandError () -> Either CommandError ())
-> IO (Either CommandError ())
-> IO (Either CommandError () -> Either CommandError ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Results () -> Connection -> Bool -> IO (Either CommandError ())
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run (Result () -> Results ()
forall a. Result a -> Results a
Decoders.Results.single Result ()
Decoders.Result.noResult) Connection
connection Bool
integerDatetimes
IO (Either CommandError () -> Either CommandError ())
-> IO (Either CommandError ()) -> IO (Either CommandError ())
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Results () -> Connection -> Bool -> IO (Either CommandError ())
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run Results ()
Decoders.Results.dropRemainders Connection
connection Bool
integerDatetimes
onOldRemoteKey :: a -> f (Either a (a, f (Either a ())))
onOldRemoteKey a
key =
Either a (a, f (Either a ())) -> f (Either a (a, f (Either a ())))
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((a, f (Either a ())) -> Either a (a, f (Either a ()))
forall a b. b -> Either a b
Right (a
key, Either a () -> f (Either a ())
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> Either a ()
forall a b. b -> Either a b
Right ())))
sendQuery :: ByteString
-> IO (Either SessionError (IO (Either SessionError result)))
sendQuery ByteString
key =
Connection
-> ByteString -> [Maybe (ByteString, Format)] -> Format -> IO Bool
Pq.sendQueryPrepared Connection
connection ByteString
key [Maybe (ByteString, Format)]
valueAndFormatList Format
Pq.Binary IO Bool
-> (Bool
-> IO (Either SessionError (IO (Either SessionError result))))
-> IO (Either SessionError (IO (Either SessionError result)))
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
False -> SessionError
-> Either SessionError (IO (Either SessionError result))
forall a b. a -> Either a b
Left (SessionError
-> Either SessionError (IO (Either SessionError result)))
-> (Maybe ByteString -> SessionError)
-> Maybe ByteString
-> Either SessionError (IO (Either SessionError result))
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CommandError -> SessionError
commandToSessionError (CommandError -> SessionError)
-> (Maybe ByteString -> CommandError)
-> Maybe ByteString
-> SessionError
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Maybe ByteString -> CommandError
ClientError (Maybe ByteString
-> Either SessionError (IO (Either SessionError result)))
-> IO (Maybe ByteString)
-> IO (Either SessionError (IO (Either SessionError result)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO (Maybe ByteString)
Pq.errorMessage Connection
connection
Bool
True -> Either SessionError (IO (Either SessionError result))
-> IO (Either SessionError (IO (Either SessionError result)))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO (Either SessionError result)
-> Either SessionError (IO (Either SessionError result))
forall a b. b -> Either a b
Right IO (Either SessionError result)
recv)
where
recv :: IO (Either SessionError result)
recv =
(Either CommandError result -> Either SessionError result)
-> IO (Either CommandError result)
-> IO (Either SessionError result)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CommandError -> SessionError)
-> Either CommandError result -> Either SessionError result
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first CommandError -> SessionError
commandToSessionError)
(IO (Either CommandError result)
-> IO (Either SessionError result))
-> IO (Either CommandError result)
-> IO (Either SessionError result)
forall a b. (a -> b) -> a -> b
$ Either CommandError result
-> Either CommandError () -> Either CommandError result
forall a b.
Either CommandError a
-> Either CommandError b -> Either CommandError a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
(<*)
(Either CommandError result
-> Either CommandError () -> Either CommandError result)
-> IO (Either CommandError result)
-> IO (Either CommandError () -> Either CommandError result)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Results result
-> Connection -> Bool -> IO (Either CommandError result)
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run Results result
decoder Connection
connection Bool
integerDatetimes
IO (Either CommandError () -> Either CommandError result)
-> IO (Either CommandError ()) -> IO (Either CommandError result)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Results () -> Connection -> Bool -> IO (Either CommandError ())
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run Results ()
Decoders.Results.dropRemainders Connection
connection Bool
integerDatetimes
runUnprepared :: IO (Either SessionError (IO (Either SessionError result)))
runUnprepared =
Connection
-> ByteString
-> [Maybe (Oid, ByteString, Format)]
-> Format
-> IO Bool
Pq.sendQueryParams Connection
connection ByteString
sql (Params params
-> Bool -> params -> [Maybe (Oid, ByteString, Format)]
forall a.
Params a -> Bool -> a -> [Maybe (Oid, ByteString, Format)]
Encoders.Params.compileUnpreparedStatementData Params params
encoder Bool
integerDatetimes params
params) Format
Pq.Binary IO Bool
-> (Bool
-> IO (Either SessionError (IO (Either SessionError result))))
-> IO (Either SessionError (IO (Either SessionError result)))
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
False -> SessionError
-> Either SessionError (IO (Either SessionError result))
forall a b. a -> Either a b
Left (SessionError
-> Either SessionError (IO (Either SessionError result)))
-> (Maybe ByteString -> SessionError)
-> Maybe ByteString
-> Either SessionError (IO (Either SessionError result))
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CommandError -> SessionError
commandToSessionError (CommandError -> SessionError)
-> (Maybe ByteString -> CommandError)
-> Maybe ByteString
-> SessionError
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Maybe ByteString -> CommandError
ClientError (Maybe ByteString
-> Either SessionError (IO (Either SessionError result)))
-> IO (Maybe ByteString)
-> IO (Either SessionError (IO (Either SessionError result)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO (Maybe ByteString)
Pq.errorMessage Connection
connection
Bool
True -> Either SessionError (IO (Either SessionError result))
-> IO (Either SessionError (IO (Either SessionError result)))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO (Either SessionError result)
-> Either SessionError (IO (Either SessionError result))
forall a b. b -> Either a b
Right IO (Either SessionError result)
recv)
where
recv :: IO (Either SessionError result)
recv =
(Either CommandError result -> Either SessionError result)
-> IO (Either CommandError result)
-> IO (Either SessionError result)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CommandError -> SessionError)
-> Either CommandError result -> Either SessionError result
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first CommandError -> SessionError
commandToSessionError)
(IO (Either CommandError result)
-> IO (Either SessionError result))
-> IO (Either CommandError result)
-> IO (Either SessionError result)
forall a b. (a -> b) -> a -> b
$ Either CommandError result
-> Either CommandError () -> Either CommandError result
forall a b.
Either CommandError a
-> Either CommandError b -> Either CommandError a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
(<*)
(Either CommandError result
-> Either CommandError () -> Either CommandError result)
-> IO (Either CommandError result)
-> IO (Either CommandError () -> Either CommandError result)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Results result
-> Connection -> Bool -> IO (Either CommandError result)
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run Results result
decoder Connection
connection Bool
integerDatetimes
IO (Either CommandError () -> Either CommandError result)
-> IO (Either CommandError ()) -> IO (Either CommandError result)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Results () -> Connection -> Bool -> IO (Either CommandError ())
forall a.
Results a -> Connection -> Bool -> IO (Either CommandError a)
Decoders.Results.run Results ()
Decoders.Results.dropRemainders Connection
connection Bool
integerDatetimes
commandToSessionError :: CommandError -> SessionError
commandToSessionError =
ByteString -> [Text] -> CommandError -> SessionError
QueryError ByteString
sql (Params params -> params -> [Text]
forall a. Params a -> a -> [Text]
Encoders.Params.renderReadable Params params
encoder params
params)