module Hasql.Private.Decoders.Results where
import qualified Database.PostgreSQL.LibPQ as LibPQ
import qualified Hasql.Private.Decoders.Result as Result
import qualified Hasql.Private.Decoders.Row as Row
import Hasql.Private.Errors
import Hasql.Private.Prelude hiding (many, maybe)
import qualified Hasql.Private.Prelude as Prelude
newtype Results a
= Results (ReaderT (Bool, LibPQ.Connection) (ExceptT CommandError IO) a)
deriving (forall a b. a -> Results b -> Results a
forall a b. (a -> b) -> Results a -> Results b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Results b -> Results a
$c<$ :: forall a b. a -> Results b -> Results a
fmap :: forall a b. (a -> b) -> Results a -> Results b
$cfmap :: forall a b. (a -> b) -> Results a -> Results b
Functor, Functor Results
forall a. a -> Results a
forall a b. Results a -> Results b -> Results a
forall a b. Results a -> Results b -> Results b
forall a b. Results (a -> b) -> Results a -> Results b
forall a b c. (a -> b -> c) -> Results a -> Results b -> Results 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
<* :: forall a b. Results a -> Results b -> Results a
$c<* :: forall a b. Results a -> Results b -> Results a
*> :: forall a b. Results a -> Results b -> Results b
$c*> :: forall a b. Results a -> Results b -> Results b
liftA2 :: forall a b c. (a -> b -> c) -> Results a -> Results b -> Results c
$cliftA2 :: forall a b c. (a -> b -> c) -> Results a -> Results b -> Results c
<*> :: forall a b. Results (a -> b) -> Results a -> Results b
$c<*> :: forall a b. Results (a -> b) -> Results a -> Results b
pure :: forall a. a -> Results a
$cpure :: forall a. a -> Results a
Applicative, Applicative Results
forall a. a -> Results a
forall a b. Results a -> Results b -> Results b
forall a b. Results a -> (a -> Results b) -> Results 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 :: forall a. a -> Results a
$creturn :: forall a. a -> Results a
>> :: forall a b. Results a -> Results b -> Results b
$c>> :: forall a b. Results a -> Results b -> Results b
>>= :: forall a b. Results a -> (a -> Results b) -> Results b
$c>>= :: forall a b. Results a -> (a -> Results b) -> Results b
Monad)
{-# INLINE run #-}
run :: Results a -> (Bool, LibPQ.Connection) -> IO (Either CommandError a)
run :: forall a.
Results a -> (Bool, Connection) -> IO (Either CommandError a)
run (Results ReaderT (Bool, Connection) (ExceptT CommandError IO) a
stack) (Bool, Connection)
env =
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT (Bool, Connection) (ExceptT CommandError IO) a
stack (Bool, Connection)
env)
{-# INLINE clientError #-}
clientError :: Results a
clientError :: forall a. Results a
clientError =
forall a.
ReaderT (Bool, Connection) (ExceptT CommandError IO) a -> Results a
Results forall a b. (a -> b) -> a -> b
$
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \(Bool
_, Connection
connection) ->
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> Either a b
Left 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) (Connection -> IO (Maybe ByteString)
LibPQ.errorMessage Connection
connection)
{-# INLINE single #-}
single :: Result.Result a -> Results a
single :: forall a. Result a -> Results a
single Result a
resultDec =
forall a.
ReaderT (Bool, Connection) (ExceptT CommandError IO) a -> Results a
Results forall a b. (a -> b) -> a -> b
$
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \(Bool
integerDatetimes, Connection
connection) -> forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$ do
Maybe Result
resultMaybe <- Connection -> IO (Maybe Result)
LibPQ.getResult Connection
connection
case Maybe Result
resultMaybe of
Just Result
result ->
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft ResultError -> CommandError
ResultError forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Result a -> (Bool, Result) -> IO (Either ResultError a)
Result.run Result a
resultDec (Bool
integerDatetimes, Result
result)
Maybe Result
Nothing ->
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> Either a b
Left 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) (Connection -> IO (Maybe ByteString)
LibPQ.errorMessage Connection
connection)
{-# INLINE getResult #-}
getResult :: Results LibPQ.Result
getResult :: Results Result
getResult =
forall a.
ReaderT (Bool, Connection) (ExceptT CommandError IO) a -> Results a
Results forall a b. (a -> b) -> a -> b
$
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \(Bool
_, Connection
connection) -> forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$ do
Maybe Result
resultMaybe <- Connection -> IO (Maybe Result)
LibPQ.getResult Connection
connection
case Maybe Result
resultMaybe of
Just Result
result -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. b -> Either a b
Right Result
result)
Maybe Result
Nothing -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> Either a b
Left 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) (Connection -> IO (Maybe ByteString)
LibPQ.errorMessage Connection
connection)
{-# INLINE getResultMaybe #-}
getResultMaybe :: Results (Maybe LibPQ.Result)
getResultMaybe :: Results (Maybe Result)
getResultMaybe =
forall a.
ReaderT (Bool, Connection) (ExceptT CommandError IO) a -> Results a
Results forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \(Bool
_, Connection
connection) -> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ Connection -> IO (Maybe Result)
LibPQ.getResult Connection
connection
{-# INLINE dropRemainders #-}
dropRemainders :: Results ()
dropRemainders :: Results ()
dropRemainders =
{-# SCC "dropRemainders" #-}
forall a.
ReaderT (Bool, Connection) (ExceptT CommandError IO) a -> Results a
Results forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \(Bool
integerDatetimes, Connection
connection) -> Bool -> Connection -> ExceptT CommandError IO ()
loop Bool
integerDatetimes Connection
connection
where
loop :: Bool -> Connection -> ExceptT CommandError IO ()
loop Bool
integerDatetimes Connection
connection =
ExceptT CommandError IO (Maybe Result)
getResultMaybe forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe (forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) Result -> ExceptT CommandError IO ()
onResult
where
getResultMaybe :: ExceptT CommandError IO (Maybe Result)
getResultMaybe =
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ Connection -> IO (Maybe Result)
LibPQ.getResult Connection
connection
onResult :: Result -> ExceptT CommandError IO ()
onResult Result
result =
Bool -> Connection -> ExceptT CommandError IO ()
loop Bool
integerDatetimes Connection
connection forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ExceptT CommandError IO ()
checkErrors
where
checkErrors :: ExceptT CommandError IO ()
checkErrors =
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft ResultError -> CommandError
ResultError) forall a b. (a -> b) -> a -> b
$ forall a. Result a -> (Bool, Result) -> IO (Either ResultError a)
Result.run Result ()
Result.noResult (Bool
integerDatetimes, Result
result)
refine :: (a -> Either Text b) -> Results a -> Results b
refine :: forall a b. (a -> Either Text b) -> Results a -> Results b
refine a -> Either Text b
refiner Results a
results = forall a.
ReaderT (Bool, Connection) (ExceptT CommandError IO) a -> Results a
Results forall a b. (a -> b) -> a -> b
$
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \(Bool, Connection)
env -> forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$ do
Either CommandError a
resultEither <- forall a.
Results a -> (Bool, Connection) -> IO (Either CommandError a)
run Results a
results (Bool, Connection)
env
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Either CommandError a
resultEither forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft (ResultError -> CommandError
ResultError forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> ResultError
UnexpectedResult) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Either Text b
refiner