module Hasql.TestingUtils.TestingDsl ( Session.Session, SessionError (..), Session.QueryError (..), Session.CommandError (..), runSessionOnLocalDb, runStatementInSession, ) where import Hasql.Connection qualified as Connection import Hasql.Session qualified as Session import Hasql.Statement qualified as Statement import Hasql.TestingUtils.Constants qualified as Constants import Prelude data SessionError = ConnectionError (Connection.ConnectionError) | SessionError (Session.QueryError) deriving (Int -> SessionError -> ShowS [SessionError] -> ShowS SessionError -> String (Int -> SessionError -> ShowS) -> (SessionError -> String) -> ([SessionError] -> ShowS) -> Show SessionError forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> SessionError -> ShowS showsPrec :: Int -> SessionError -> ShowS $cshow :: SessionError -> String show :: SessionError -> String $cshowList :: [SessionError] -> ShowS showList :: [SessionError] -> ShowS Show, SessionError -> SessionError -> Bool (SessionError -> SessionError -> Bool) -> (SessionError -> SessionError -> Bool) -> Eq SessionError forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: SessionError -> SessionError -> Bool == :: SessionError -> SessionError -> Bool $c/= :: SessionError -> SessionError -> Bool /= :: SessionError -> SessionError -> Bool Eq) runSessionOnLocalDb :: Session.Session a -> IO (Either SessionError a) runSessionOnLocalDb :: forall a. Session a -> IO (Either SessionError a) runSessionOnLocalDb Session a session = ExceptT SessionError IO a -> IO (Either SessionError a) forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a) runExceptT (ExceptT SessionError IO a -> IO (Either SessionError a)) -> ExceptT SessionError IO a -> IO (Either SessionError a) forall a b. (a -> b) -> a -> b $ ExceptT SessionError IO Connection acquire ExceptT SessionError IO Connection -> (Connection -> ExceptT SessionError IO a) -> ExceptT SessionError IO a 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 >>= \Connection connection -> Connection -> ExceptT SessionError IO a use Connection connection ExceptT SessionError IO a -> ExceptT SessionError IO () -> ExceptT SessionError IO a forall a b. ExceptT SessionError IO a -> ExceptT SessionError IO b -> ExceptT SessionError IO a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* Connection -> ExceptT SessionError IO () forall {t :: (* -> *) -> * -> *}. MonadTrans t => Connection -> t IO () release Connection connection where acquire :: ExceptT SessionError IO Connection acquire = IO (Either SessionError Connection) -> ExceptT SessionError IO Connection forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a ExceptT (IO (Either SessionError Connection) -> ExceptT SessionError IO Connection) -> IO (Either SessionError Connection) -> ExceptT SessionError IO Connection forall a b. (a -> b) -> a -> b $ (Either ConnectionError Connection -> Either SessionError Connection) -> IO (Either ConnectionError Connection) -> IO (Either SessionError Connection) forall a b. (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((ConnectionError -> SessionError) -> Either ConnectionError Connection -> Either SessionError Connection forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c mapLeft ConnectionError -> SessionError ConnectionError) (IO (Either ConnectionError Connection) -> IO (Either SessionError Connection)) -> IO (Either ConnectionError Connection) -> IO (Either SessionError Connection) forall a b. (a -> b) -> a -> b $ ByteString -> IO (Either ConnectionError Connection) Connection.acquire ByteString Constants.localConnectionSettings use :: Connection -> ExceptT SessionError IO a use Connection connection = 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 QueryError a -> Either SessionError a) -> IO (Either QueryError 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 ((QueryError -> SessionError) -> Either QueryError a -> Either SessionError a forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c mapLeft QueryError -> SessionError SessionError) (IO (Either QueryError a) -> IO (Either SessionError a)) -> IO (Either QueryError a) -> IO (Either SessionError a) forall a b. (a -> b) -> a -> b $ Session a -> Connection -> IO (Either QueryError a) forall a. Session a -> Connection -> IO (Either QueryError a) Session.run Session a session Connection connection release :: Connection -> t IO () release Connection connection = IO () -> t IO () forall (m :: * -> *) a. Monad m => m a -> t m a forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> t IO ()) -> IO () -> t IO () forall a b. (a -> b) -> a -> b $ Connection -> IO () Connection.release Connection connection runStatementInSession :: Statement.Statement a b -> a -> Session.Session b runStatementInSession :: forall a b. Statement a b -> a -> Session b runStatementInSession Statement a b statement a params = a -> Statement a b -> Session b forall params result. params -> Statement params result -> Session result Session.statement a params Statement a b statement