Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module is where Squeal commands actually get executed by
LibPQ
. It containts two typeclasses, IndexedMonadTransPQ
for executing
a Definition
and MonadPQ
for executing a Manipulation
or Query
,
and a PQ
type with instances for them.
Using Squeal in your application will come down to defining
the schemas
of your database and including PQ schemas schemas
in your
application's monad transformer stack, giving it an instance of MonadPQ
.
This module also provides functions for retrieving rows from the Result
of executing Squeal commands.
Synopsis
- data Connection
- connectdb :: forall schemas io. MonadIO io => ByteString -> io (K Connection schemas)
- finish :: MonadIO io => K Connection schemas -> io ()
- withConnection :: forall schemas0 schemas1 io x. MonadUnliftIO io => ByteString -> PQ schemas0 schemas1 io x -> io x
- lowerConnection :: K Connection (schema ': schemas) -> K Connection schemas
- newtype PQ (schemas0 :: SchemasType) (schemas1 :: SchemasType) (m :: Type -> Type) (x :: Type) = PQ {
- unPQ :: K Connection schemas0 -> m (K x schemas1)
- runPQ :: Functor m => PQ schemas0 schemas1 m x -> K Connection schemas0 -> m (x, K Connection schemas1)
- execPQ :: Functor m => PQ schemas0 schemas1 m x -> K Connection schemas0 -> m (K Connection schemas1)
- evalPQ :: Functor m => PQ schemas0 schemas1 m x -> K Connection schemas0 -> m x
- class IndexedMonadTransPQ pq where
- pqAp :: Monad m => pq schemas0 schemas1 m (x -> y) -> pq schemas1 schemas2 m x -> pq schemas0 schemas2 m y
- pqJoin :: Monad m => pq schemas0 schemas1 m (pq schemas1 schemas2 m y) -> pq schemas0 schemas2 m y
- pqBind :: Monad m => (x -> pq schemas1 schemas2 m y) -> pq schemas0 schemas1 m x -> pq schemas0 schemas2 m y
- pqThen :: Monad m => pq schemas1 schemas2 m y -> pq schemas0 schemas1 m x -> pq schemas0 schemas2 m y
- pqAndThen :: Monad m => (y -> pq schemas1 schemas2 m z) -> (x -> pq schemas0 schemas1 m y) -> x -> pq schemas0 schemas2 m z
- define :: MonadIO io => Definition schemas0 schemas1 -> pq schemas0 schemas1 io ()
- class Monad pq => MonadPQ schemas pq | pq -> schemas where
- manipulateParams :: ToParams x params => Manipulation '[] schemas params ys -> x -> pq (K Result ys)
- manipulateParams_ :: ToParams x params => Manipulation '[] schemas params '[] -> x -> pq ()
- manipulate :: Manipulation '[] schemas '[] ys -> pq (K Result ys)
- manipulate_ :: Manipulation '[] schemas '[] '[] -> pq ()
- runQueryParams :: ToParams x params => Query '[] '[] schemas params ys -> x -> pq (K Result ys)
- runQuery :: Query '[] '[] schemas '[] ys -> pq (K Result ys)
- traversePrepared :: (ToParams x params, Traversable list) => Manipulation '[] schemas params ys -> list x -> pq (list (K Result ys))
- forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation '[] schemas params ys -> pq (list (K Result ys))
- traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation '[] schemas params '[] -> list x -> pq ()
- forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation '[] schemas params '[] -> pq ()
- liftPQ :: (Connection -> IO a) -> pq a
- data Result
- data Row
- ntuples :: MonadIO io => K Result columns -> io Row
- getRow :: (FromRow columns y, MonadIO io) => Row -> K Result columns -> io y
- getRows :: (FromRow columns y, MonadIO io) => K Result columns -> io [y]
- nextRow :: (FromRow columns y, MonadIO io) => Row -> K Result columns -> Row -> io (Maybe (Row, y))
- firstRow :: (FromRow columns y, MonadIO io) => K Result columns -> io (Maybe y)
- liftResult :: MonadIO io => (Result -> IO x) -> K Result results -> io x
- data ExecStatus
- resultStatus :: MonadIO io => K Result results -> io ExecStatus
- resultErrorMessage :: MonadIO io => K Result results -> io (Maybe ByteString)
- resultErrorCode :: MonadIO io => K Result results -> io (Maybe ByteString)
- data SquealException
- data PQState = PQState {}
- okResult :: MonadIO io => K Result row -> io ()
- catchSqueal :: MonadUnliftIO io => io a -> (SquealException -> io a) -> io a
- handleSqueal :: MonadUnliftIO io => (SquealException -> io a) -> io a -> io a
- trySqueal :: MonadUnliftIO io => io a -> io (Either SquealException a)
Connection
data Connection #
Connection
encapsulates a connection to the backend.
Instances
Eq Connection | |
Defined in Database.PostgreSQL.LibPQ.Internal (==) :: Connection -> Connection -> Bool # (/=) :: Connection -> Connection -> Bool # |
:: MonadIO io | |
=> ByteString | conninfo |
-> io (K Connection schemas) |
Makes a new connection to the database server.
This function opens a new database connection using the parameters taken from the string conninfo.
The passed string can be empty to use all default parameters, or it can contain one or more parameter settings separated by whitespace. Each parameter setting is in the form keyword = value. Spaces around the equal sign are optional. To write an empty value or a value containing spaces, surround it with single quotes, e.g., keyword = 'a value'. Single quotes and backslashes within the value must be escaped with a backslash, i.e., ' and .
To specify the schema you wish to connect with, use type application.
>>>
:set -XDataKinds
>>>
:set -XPolyKinds
>>>
:set -XTypeOperators
>>>
type Schema = '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint2]]
>>>
:set -XTypeApplications
>>>
:set -XOverloadedStrings
>>>
conn <- connectdb @Schema "host=localhost port=5432 dbname=exampledb"
Note that, for now, squeal doesn't offer any protection from connecting with the wrong schema!
withConnection :: forall schemas0 schemas1 io x. MonadUnliftIO io => ByteString -> PQ schemas0 schemas1 io x -> io x Source #
lowerConnection :: K Connection (schema ': schemas) -> K Connection schemas Source #
Safely lowerConnection
to a smaller schema.
PQ
newtype PQ (schemas0 :: SchemasType) (schemas1 :: SchemasType) (m :: Type -> Type) (x :: Type) Source #
We keep track of the schema via an Atkey indexed state monad transformer,
PQ
.
PQ | |
|
Instances
IndexedMonadTransPQ PQ Source # | |
Defined in Squeal.PostgreSQL.PQ pqAp :: Monad m => PQ schemas0 schemas1 m (x -> y) -> PQ schemas1 schemas2 m x -> PQ schemas0 schemas2 m y Source # pqJoin :: Monad m => PQ schemas0 schemas1 m (PQ schemas1 schemas2 m y) -> PQ schemas0 schemas2 m y Source # pqBind :: Monad m => (x -> PQ schemas1 schemas2 m y) -> PQ schemas0 schemas1 m x -> PQ schemas0 schemas2 m y Source # pqThen :: Monad m => PQ schemas1 schemas2 m y -> PQ schemas0 schemas1 m x -> PQ schemas0 schemas2 m y Source # pqAndThen :: Monad m => (y -> PQ schemas1 schemas2 m z) -> (x -> PQ schemas0 schemas1 m y) -> x -> PQ schemas0 schemas2 m z Source # define :: MonadIO io => Definition schemas0 schemas1 -> PQ schemas0 schemas1 io () Source # | |
schemas0 ~ schemas1 => MFunctor (PQ schemas0 schemas1 :: (Type -> Type) -> Type -> Type) Source # | |
(MonadIO io, schemas0 ~ schemas, schemas1 ~ schemas) => MonadPQ schemas (PQ schemas0 schemas1 io) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> PQ schemas0 schemas1 io (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> PQ schemas0 schemas1 io () Source # manipulate :: Manipulation [] schemas [] ys -> PQ schemas0 schemas1 io (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> PQ schemas0 schemas1 io () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> PQ schemas0 schemas1 io (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> PQ schemas0 schemas1 io (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> PQ schemas0 schemas1 io (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> PQ schemas0 schemas1 io (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> PQ schemas0 schemas1 io () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> PQ schemas0 schemas1 io () Source # liftPQ :: (Connection -> IO a) -> PQ schemas0 schemas1 io a Source # | |
schemas0 ~ schemas1 => MonadTrans (PQ schemas0 schemas1) Source # | |
Defined in Squeal.PostgreSQL.PQ | |
schemas0 ~ schemas1 => MMonad (PQ schemas0 schemas1) Source # | |
(Monad m, schemas0 ~ schemas1) => Monad (PQ schemas0 schemas1 m) Source # | |
Defined in Squeal.PostgreSQL.PQ | |
Monad m => Functor (PQ schemas0 schemas1 m) Source # | |
(Monad m, schemas0 ~ schemas1) => MonadFail (PQ schemas0 schemas1 m) Source # | |
Defined in Squeal.PostgreSQL.PQ | |
(Monad m, schemas0 ~ schemas1) => Applicative (PQ schemas0 schemas1 m) Source # | |
Defined in Squeal.PostgreSQL.PQ pure :: a -> PQ schemas0 schemas1 m a # (<*>) :: PQ schemas0 schemas1 m (a -> b) -> PQ schemas0 schemas1 m a -> PQ schemas0 schemas1 m b # liftA2 :: (a -> b -> c) -> PQ schemas0 schemas1 m a -> PQ schemas0 schemas1 m b -> PQ schemas0 schemas1 m c # (*>) :: PQ schemas0 schemas1 m a -> PQ schemas0 schemas1 m b -> PQ schemas0 schemas1 m b # (<*) :: PQ schemas0 schemas1 m a -> PQ schemas0 schemas1 m b -> PQ schemas0 schemas1 m a # | |
(MonadIO m, schema0 ~ schema1) => MonadIO (PQ schema0 schema1 m) Source # | |
Defined in Squeal.PostgreSQL.PQ | |
(MonadUnliftIO m, schemas0 ~ schemas1) => MonadUnliftIO (PQ schemas0 schemas1 m) Source # | |
Defined in Squeal.PostgreSQL.PQ | |
Migratory (Terminally PQ IO) Source # | |
Defined in Squeal.PostgreSQL.Migration migrateUp :: AlignedList (Migration (Terminally PQ IO)) schemas0 schemas1 -> PQ schemas0 schemas1 IO () Source # migrateDown :: AlignedList (Migration (Terminally PQ IO)) schemas0 schemas1 -> PQ schemas1 schemas0 IO () Source # |
runPQ :: Functor m => PQ schemas0 schemas1 m x -> K Connection schemas0 -> m (x, K Connection schemas1) Source #
Run a PQ
and keep the result and the Connection
.
execPQ :: Functor m => PQ schemas0 schemas1 m x -> K Connection schemas0 -> m (K Connection schemas1) Source #
Execute a PQ
and discard the result but keep the Connection
.
evalPQ :: Functor m => PQ schemas0 schemas1 m x -> K Connection schemas0 -> m x Source #
Evaluate a PQ
and discard the Connection
but keep the result.
class IndexedMonadTransPQ pq where Source #
An Atkey indexed monad is a Functor
enriched category.
An indexed monad transformer transforms a Monad
into an indexed monad.
And, IndexedMonadTransPQ
is a class for indexed monad transformers that
support running Definition
s using define
.
pqAp :: Monad m => pq schemas0 schemas1 m (x -> y) -> pq schemas1 schemas2 m x -> pq schemas0 schemas2 m y Source #
indexed analog of <*>
pqJoin :: Monad m => pq schemas0 schemas1 m (pq schemas1 schemas2 m y) -> pq schemas0 schemas2 m y Source #
indexed analog of join
pqBind :: Monad m => (x -> pq schemas1 schemas2 m y) -> pq schemas0 schemas1 m x -> pq schemas0 schemas2 m y Source #
indexed analog of =<<
pqThen :: Monad m => pq schemas1 schemas2 m y -> pq schemas0 schemas1 m x -> pq schemas0 schemas2 m y Source #
indexed analog of flipped >>
pqAndThen :: Monad m => (y -> pq schemas1 schemas2 m z) -> (x -> pq schemas0 schemas1 m y) -> x -> pq schemas0 schemas2 m z Source #
indexed analog of <=<
define :: MonadIO io => Definition schemas0 schemas1 -> pq schemas0 schemas1 io () Source #
Run a Definition
with exec
.
It should be functorial in effect.
define id = return ()
define (statement1 >>> statement2) = define statement1 & pqThen (define statement2)
Instances
IndexedMonadTransPQ PQ Source # | |
Defined in Squeal.PostgreSQL.PQ pqAp :: Monad m => PQ schemas0 schemas1 m (x -> y) -> PQ schemas1 schemas2 m x -> PQ schemas0 schemas2 m y Source # pqJoin :: Monad m => PQ schemas0 schemas1 m (PQ schemas1 schemas2 m y) -> PQ schemas0 schemas2 m y Source # pqBind :: Monad m => (x -> PQ schemas1 schemas2 m y) -> PQ schemas0 schemas1 m x -> PQ schemas0 schemas2 m y Source # pqThen :: Monad m => PQ schemas1 schemas2 m y -> PQ schemas0 schemas1 m x -> PQ schemas0 schemas2 m y Source # pqAndThen :: Monad m => (y -> PQ schemas1 schemas2 m z) -> (x -> PQ schemas0 schemas1 m y) -> x -> PQ schemas0 schemas2 m z Source # define :: MonadIO io => Definition schemas0 schemas1 -> PQ schemas0 schemas1 io () Source # |
class Monad pq => MonadPQ schemas pq | pq -> schemas where Source #
MonadPQ
is an mtl
style constraint, similar to
MonadState
, for using LibPQ
to
manipulateParams
runs aManipulation
with params from a type with aToParams
constraint. It callsexecParams
and doesn't afraid of anything.manipulateParams_
is likemanipulateParams
for a returning-free statement.manipulate
is likemanipulateParams
for a parameter-free statement.manipulate_
is likemanipulate
for a returning-free statement.runQueryParams
is likemanipulateParams
for query statements.runQuery
is likerunQueryParams
for a parameter-free statement.traversePrepared
has the same type signature as a composition oftraverse
andmanipulateParams
but provides an optimization by preparing the statement withprepare
and then traversing aTraversable
container withexecPrepared
. The temporary prepared statement is then deallocated.forPrepared
is a flippedtraversePrepared
traversePrepared_
is liketraversePrepared
but works onFoldable
containers for a returning-free statement.forPrepared_
is a flippedtraversePrepared_
.liftPQ
lets you lift actions fromLibPQ
that require a connection into your monad.
To define an instance, you can minimally define only manipulateParams
,
traversePrepared
, traversePrepared_
and liftPQ
. Monad transformers get
a default instance.
Nothing
:: ToParams x params | |
=> Manipulation '[] schemas params ys | |
-> x | |
-> pq (K Result ys) |
:: (MonadTrans t, MonadPQ schemas pq1, pq ~ t pq1) | |
=> ToParams x params | |
=> Manipulation '[] schemas params ys | |
-> x | |
-> pq (K Result ys) |
:: ToParams x params | |
=> Manipulation '[] schemas params '[] | |
-> x | |
-> pq () |
manipulate :: Manipulation '[] schemas '[] ys -> pq (K Result ys) Source #
manipulate_ :: Manipulation '[] schemas '[] '[] -> pq () Source #
:: (ToParams x params, Traversable list) | |
=> Manipulation '[] schemas params ys |
|
-> list x | |
-> pq (list (K Result ys)) |
:: (MonadTrans t, MonadPQ schemas pq1, pq ~ t pq1) | |
=> (ToParams x params, Traversable list) | |
=> Manipulation '[] schemas params ys |
|
-> list x | |
-> pq (list (K Result ys)) |
:: (ToParams x params, Traversable list) | |
=> list x | |
-> Manipulation '[] schemas params ys | |
-> pq (list (K Result ys)) |
:: (ToParams x params, Foldable list) | |
=> Manipulation '[] schemas params '[] | |
-> list x | |
-> pq () |
:: (MonadTrans t, MonadPQ schemas pq1, pq ~ t pq1) | |
=> (ToParams x params, Foldable list) | |
=> Manipulation '[] schemas params '[] | |
-> list x | |
-> pq () |
:: (ToParams x params, Foldable list) | |
=> list x | |
-> Manipulation '[] schemas params '[] | |
-> pq () |
liftPQ :: (Connection -> IO a) -> pq a Source #
liftPQ :: (MonadTrans t, MonadPQ schemas pq1, pq ~ t pq1) => (Connection -> IO a) -> pq a Source #
Instances
MonadPQ schemas m => MonadPQ schemas (MaybeT m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> MaybeT m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> MaybeT m () Source # manipulate :: Manipulation [] schemas [] ys -> MaybeT m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> MaybeT m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> MaybeT m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> MaybeT m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> MaybeT m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> MaybeT m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> MaybeT m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> MaybeT m () Source # | |
MonadPQ schemas m => MonadPQ schemas (ExceptT e m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> ExceptT e m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> ExceptT e m () Source # manipulate :: Manipulation [] schemas [] ys -> ExceptT e m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> ExceptT e m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> ExceptT e m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> ExceptT e m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> ExceptT e m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> ExceptT e m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> ExceptT e m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> ExceptT e m () Source # | |
(Monoid w, MonadPQ schemas m) => MonadPQ schemas (WriterT w m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> WriterT w m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> WriterT w m () Source # manipulate :: Manipulation [] schemas [] ys -> WriterT w m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> WriterT w m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> WriterT w m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> WriterT w m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> WriterT w m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> WriterT w m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> WriterT w m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> WriterT w m () Source # | |
(Monoid w, MonadPQ schemas m) => MonadPQ schemas (WriterT w m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> WriterT w m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> WriterT w m () Source # manipulate :: Manipulation [] schemas [] ys -> WriterT w m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> WriterT w m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> WriterT w m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> WriterT w m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> WriterT w m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> WriterT w m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> WriterT w m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> WriterT w m () Source # | |
MonadPQ schemas m => MonadPQ schemas (StateT s m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> StateT s m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> StateT s m () Source # manipulate :: Manipulation [] schemas [] ys -> StateT s m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> StateT s m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> StateT s m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> StateT s m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> StateT s m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> StateT s m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> StateT s m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> StateT s m () Source # | |
MonadPQ schemas m => MonadPQ schemas (StateT s m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> StateT s m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> StateT s m () Source # manipulate :: Manipulation [] schemas [] ys -> StateT s m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> StateT s m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> StateT s m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> StateT s m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> StateT s m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> StateT s m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> StateT s m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> StateT s m () Source # | |
MonadPQ schemas m => MonadPQ schemas (IdentityT m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> IdentityT m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> IdentityT m () Source # manipulate :: Manipulation [] schemas [] ys -> IdentityT m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> IdentityT m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> IdentityT m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> IdentityT m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> IdentityT m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> IdentityT m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> IdentityT m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> IdentityT m () Source # | |
MonadPQ schemas m => MonadPQ schemas (ContT r m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> ContT r m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> ContT r m () Source # manipulate :: Manipulation [] schemas [] ys -> ContT r m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> ContT r m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> ContT r m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> ContT r m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> ContT r m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> ContT r m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> ContT r m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> ContT r m () Source # | |
MonadPQ schemas m => MonadPQ schemas (ReaderT r m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> ReaderT r m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> ReaderT r m () Source # manipulate :: Manipulation [] schemas [] ys -> ReaderT r m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> ReaderT r m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> ReaderT r m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> ReaderT r m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> ReaderT r m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> ReaderT r m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> ReaderT r m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> ReaderT r m () Source # | |
(MonadIO io, schemas0 ~ schemas, schemas1 ~ schemas) => MonadPQ schemas (PQ schemas0 schemas1 io) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> PQ schemas0 schemas1 io (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> PQ schemas0 schemas1 io () Source # manipulate :: Manipulation [] schemas [] ys -> PQ schemas0 schemas1 io (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> PQ schemas0 schemas1 io () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> PQ schemas0 schemas1 io (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> PQ schemas0 schemas1 io (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> PQ schemas0 schemas1 io (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> PQ schemas0 schemas1 io (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> PQ schemas0 schemas1 io () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> PQ schemas0 schemas1 io () Source # liftPQ :: (Connection -> IO a) -> PQ schemas0 schemas1 io a Source # | |
(Monoid w, MonadPQ schemas m) => MonadPQ schemas (RWST r w s m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> RWST r w s m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> RWST r w s m () Source # manipulate :: Manipulation [] schemas [] ys -> RWST r w s m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> RWST r w s m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> RWST r w s m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> RWST r w s m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> RWST r w s m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> RWST r w s m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> RWST r w s m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> RWST r w s m () Source # | |
(Monoid w, MonadPQ schemas m) => MonadPQ schemas (RWST r w s m) Source # | |
Defined in Squeal.PostgreSQL.PQ manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> RWST r w s m (K Result ys) Source # manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> RWST r w s m () Source # manipulate :: Manipulation [] schemas [] ys -> RWST r w s m (K Result ys) Source # manipulate_ :: Manipulation [] schemas [] [] -> RWST r w s m () Source # runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> RWST r w s m (K Result ys) Source # runQuery :: Query [] [] schemas [] ys -> RWST r w s m (K Result ys) Source # traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> RWST r w s m (list (K Result ys)) Source # forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> RWST r w s m (list (K Result ys)) Source # traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> RWST r w s m () Source # forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> RWST r w s m () Source # |
Results
ntuples :: MonadIO io => K Result columns -> io Row Source #
Returns the number of rows (tuples) in the query result.
Get a row corresponding to a given row number from a Result
,
throwing an exception if the row number is out of bounds.
Get all rows from a Result
.
Get the first row if possible from a Result
.
liftResult :: MonadIO io => (Result -> IO x) -> K Result results -> io x Source #
Lifts actions on results from LibPQ
.
data ExecStatus #
EmptyQuery | The string sent to the server was empty. |
CommandOk | Successful completion of a command returning no data. |
TuplesOk | Successful completion of a command returning data (such as a SELECT or SHOW). |
CopyOut | Copy Out (from server) data transfer started. |
CopyIn | Copy In (to server) data transfer started. |
CopyBoth | Copy In/Out data transfer started. |
BadResponse | The server's response was not understood. |
NonfatalError | A nonfatal error (a notice or warning) occurred. |
FatalError | A fatal error occurred. |
SingleTuple | The PGresult contains a single result tuple from the current command. This status occurs only when single-row mode has been selected for the query. |
Instances
Enum ExecStatus | |
Defined in Database.PostgreSQL.LibPQ succ :: ExecStatus -> ExecStatus # pred :: ExecStatus -> ExecStatus # toEnum :: Int -> ExecStatus # fromEnum :: ExecStatus -> Int # enumFrom :: ExecStatus -> [ExecStatus] # enumFromThen :: ExecStatus -> ExecStatus -> [ExecStatus] # enumFromTo :: ExecStatus -> ExecStatus -> [ExecStatus] # enumFromThenTo :: ExecStatus -> ExecStatus -> ExecStatus -> [ExecStatus] # | |
Eq ExecStatus | |
Defined in Database.PostgreSQL.LibPQ (==) :: ExecStatus -> ExecStatus -> Bool # (/=) :: ExecStatus -> ExecStatus -> Bool # | |
Show ExecStatus | |
Defined in Database.PostgreSQL.LibPQ showsPrec :: Int -> ExecStatus -> ShowS # show :: ExecStatus -> String # showList :: [ExecStatus] -> ShowS # |
resultStatus :: MonadIO io => K Result results -> io ExecStatus Source #
Returns the result status of the command.
resultErrorMessage :: MonadIO io => K Result results -> io (Maybe ByteString) Source #
Returns the error message most recently generated by an operation on the connection.
resultErrorCode :: MonadIO io => K Result results -> io (Maybe ByteString) Source #
Returns the error code most recently generated by an operation on the connection.
https://www.postgresql.org/docs/current/static/errcodes-appendix.html
Exceptions
data SquealException Source #
Exception
s that can be thrown by Squeal.
Instances
Eq SquealException Source # | |
Defined in Squeal.PostgreSQL.PQ (==) :: SquealException -> SquealException -> Bool # (/=) :: SquealException -> SquealException -> Bool # | |
Show SquealException Source # | |
Defined in Squeal.PostgreSQL.PQ showsPrec :: Int -> SquealException -> ShowS # show :: SquealException -> String # showList :: [SquealException] -> ShowS # | |
Exception SquealException Source # | |
Defined in Squeal.PostgreSQL.PQ |
the state of LibPQ
okResult :: MonadIO io => K Result row -> io () Source #
Check if a Result
's status is either CommandOk
or TuplesOk
otherwise throw
a PQException
.
:: MonadUnliftIO io | |
=> io a | |
-> (SquealException -> io a) | handler |
-> io a |
Catch SquealException
s.
:: MonadUnliftIO io | |
=> (SquealException -> io a) | handler |
-> io a | |
-> io a |
Handle SquealException
s.
trySqueal :: MonadUnliftIO io => io a -> io (Either SquealException a) Source #
Either
return a SquealException
or a result.