squeal-postgresql-0.2.1.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2017
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.PQ

Contents

Description

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 schema of your database and including PQ schema schema 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

Connection

data Connection :: * #

Connection encapsulates a connection to the backend.

connectdb Source #

Arguments

:: MonadBase IO io 
=> ByteString

conninfo

-> io (K Connection schema) 

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!

finish :: MonadBase IO io => K Connection schema -> io () Source #

Closes the connection to the server.

withConnection :: forall schema0 schema1 io x. MonadBaseControl IO io => ByteString -> PQ schema0 schema1 io x -> io x Source #

Do connectdb and finish before and after a computation.

lowerConnection :: K Connection (table ': schema) -> K Connection schema Source #

Safely lowerConnection to a smaller schema.

PQ

newtype PQ (schema0 :: TablesType) (schema1 :: TablesType) (m :: Type -> Type) (x :: Type) Source #

We keep track of the schema via an Atkey indexed state monad transformer, PQ.

Constructors

PQ 

Fields

Instances

IndexedMonadTransPQ PQ Source # 

Methods

pqAp :: Monad m => PQ schema0 schema1 m (x -> y) -> PQ schema1 schema2 m x -> PQ schema0 schema2 m y Source #

pqJoin :: Monad m => PQ schema0 schema1 m (PQ schema1 schema2 m y) -> PQ schema0 schema2 m y Source #

pqBind :: Monad m => (x -> PQ schema1 schema2 m y) -> PQ schema0 schema1 m x -> PQ schema0 schema2 m y Source #

pqThen :: Monad m => PQ schema1 schema2 m y -> PQ schema0 schema1 m x -> PQ schema0 schema2 m y Source #

pqEmbed :: Monad m => PQ schema0 schema1 m x -> PQ (((Symbol, TableType) ': table) schema0) (((Symbol, TableType) ': table) schema1) m x Source #

define :: MonadBase IO io => Definition schema0 schema1 -> PQ schema0 schema1 io (K [k] Result [k]) Source #

(~) TablesType schema0 schema1 => MFunctor Type (PQ schema0 schema1) Source # 

Methods

hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b #

(MonadBase b m, (~) TablesType schema0 schema1) => MonadBase b (PQ schema0 schema1 m) Source # 

Methods

liftBase :: b α -> PQ schema0 schema1 m α #

(MonadBaseControl b m, (~) TablesType schema0 schema1) => MonadBaseControl b (PQ schema0 schema1 m) Source # 

Associated Types

type StM (PQ schema0 schema1 m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (PQ schema0 schema1 m) b -> b a) -> PQ schema0 schema1 m a #

restoreM :: StM (PQ schema0 schema1 m) a -> PQ schema0 schema1 m a #

(MonadBase IO io, (~) TablesType schema0 schema, (~) TablesType schema1 schema) => MonadPQ schema (PQ schema0 schema1 io) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> PQ schema0 schema1 io (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> PQ schema0 schema1 io (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> PQ schema0 schema1 io (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> PQ schema0 schema1 io (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> PQ schema0 schema1 io (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> PQ schema0 schema1 io (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> PQ schema0 schema1 io () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> PQ schema0 schema1 io () Source #

liftPQ :: (Connection -> IO a) -> PQ schema0 schema1 io a Source #

(~) TablesType schema0 schema1 => MonadTrans (PQ schema0 schema1) Source # 

Methods

lift :: Monad m => m a -> PQ schema0 schema1 m a #

(~) TablesType schema0 schema1 => MMonad (PQ schema0 schema1) Source # 

Methods

embed :: Monad n => (forall a. m a -> PQ schema0 schema1 n a) -> PQ schema0 schema1 m b -> PQ schema0 schema1 n b #

(Monad m, (~) TablesType schema0 schema1) => Monad (PQ schema0 schema1 m) Source # 

Methods

(>>=) :: PQ schema0 schema1 m a -> (a -> PQ schema0 schema1 m b) -> PQ schema0 schema1 m b #

(>>) :: PQ schema0 schema1 m a -> PQ schema0 schema1 m b -> PQ schema0 schema1 m b #

return :: a -> PQ schema0 schema1 m a #

fail :: String -> PQ schema0 schema1 m a #

Monad m => Functor (PQ schema0 schema1 m) Source # 

Methods

fmap :: (a -> b) -> PQ schema0 schema1 m a -> PQ schema0 schema1 m b #

(<$) :: a -> PQ schema0 schema1 m b -> PQ schema0 schema1 m a #

(Monad m, (~) TablesType schema0 schema1) => Applicative (PQ schema0 schema1 m) Source # 

Methods

pure :: a -> PQ schema0 schema1 m a #

(<*>) :: PQ schema0 schema1 m (a -> b) -> PQ schema0 schema1 m a -> PQ schema0 schema1 m b #

liftA2 :: (a -> b -> c) -> PQ schema0 schema1 m a -> PQ schema0 schema1 m b -> PQ schema0 schema1 m c #

(*>) :: PQ schema0 schema1 m a -> PQ schema0 schema1 m b -> PQ schema0 schema1 m b #

(<*) :: PQ schema0 schema1 m a -> PQ schema0 schema1 m b -> PQ schema0 schema1 m a #

type StM (PQ schema0 schema1 m) x Source # 
type StM (PQ schema0 schema1 m) x = StM m (K TablesType x schema0)

runPQ :: Functor m => PQ schema0 schema1 m x -> K Connection schema0 -> m (x, K Connection schema1) Source #

Run a PQ and keep the result and the Connection.

execPQ :: Functor m => PQ schema0 schema1 m x -> K Connection schema0 -> m (K Connection schema1) Source #

Execute a PQ and discard the result but keep the Connection.

evalPQ :: Functor m => PQ schema0 schema1 m x -> K Connection schema0 -> 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 Definitions using define and embedding a computation in a larger schema using pqEmbed.

Minimal complete definition

pqAp, pqJoin, pqBind, pqThen, pqEmbed, define

Methods

pqAp :: Monad m => pq schema0 schema1 m (x -> y) -> pq schema1 schema2 m x -> pq schema0 schema2 m y Source #

indexed analog of <*>

pqJoin :: Monad m => pq schema0 schema1 m (pq schema1 schema2 m y) -> pq schema0 schema2 m y Source #

indexed analog of join

pqBind :: Monad m => (x -> pq schema1 schema2 m y) -> pq schema0 schema1 m x -> pq schema0 schema2 m y Source #

indexed analog of =<<

pqThen :: Monad m => pq schema1 schema2 m y -> pq schema0 schema1 m x -> pq schema0 schema2 m y Source #

indexed analog of flipped >>

pqEmbed :: Monad m => pq schema0 schema1 m x -> pq (table ': schema0) (table ': schema1) m x Source #

Safely embed a computation in a larger schema.

define :: MonadBase IO io => Definition schema0 schema1 -> pq schema0 schema1 io (K Result '[]) Source #

Run a Definition with exec, we expect that libpq obeys the law

define statement1 & pqThen (define statement2) = define (statement1 >>> statement2)

Instances

IndexedMonadTransPQ PQ Source # 

Methods

pqAp :: Monad m => PQ schema0 schema1 m (x -> y) -> PQ schema1 schema2 m x -> PQ schema0 schema2 m y Source #

pqJoin :: Monad m => PQ schema0 schema1 m (PQ schema1 schema2 m y) -> PQ schema0 schema2 m y Source #

pqBind :: Monad m => (x -> PQ schema1 schema2 m y) -> PQ schema0 schema1 m x -> PQ schema0 schema2 m y Source #

pqThen :: Monad m => PQ schema1 schema2 m y -> PQ schema0 schema1 m x -> PQ schema0 schema2 m y Source #

pqEmbed :: Monad m => PQ schema0 schema1 m x -> PQ (((Symbol, TableType) ': table) schema0) (((Symbol, TableType) ': table) schema1) m x Source #

define :: MonadBase IO io => Definition schema0 schema1 -> PQ schema0 schema1 io (K [k] Result [k]) Source #

class Monad pq => MonadPQ schema pq | pq -> schema where Source #

MonadPQ is an mtl style constraint, similar to MonadState, for using LibPQ to

To define an instance, you can minimally define only manipulateParams, traversePrepared, traversePrepared_ and liftPQ. Monad transformers get a default instance.

Methods

manipulateParams Source #

Arguments

:: ToParams x params 
=> Manipulation schema params ys

insertRows, update or deleteFrom

-> x 
-> pq (K Result ys) 

manipulateParams Source #

Arguments

:: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) 
=> ToParams x params 
=> Manipulation schema params ys

insertRows, update or deleteFrom

-> x 
-> pq (K Result ys) 

manipulate :: Manipulation schema '[] ys -> pq (K Result ys) Source #

runQueryParams Source #

Arguments

:: ToParams x params 
=> Query schema params ys

select and friends

-> x 
-> pq (K Result ys) 

runQuery Source #

Arguments

:: Query schema '[] ys

select and friends

-> pq (K Result ys) 

traversePrepared Source #

Arguments

:: (ToParams x params, Traversable list) 
=> Manipulation schema params ys

insertRows, update, or deleteFrom, and friends

-> list x 
-> pq (list (K Result ys)) 

traversePrepared Source #

Arguments

:: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) 
=> (ToParams x params, Traversable list) 
=> Manipulation schema params ys

insertRows, update, or deleteFrom, and friends

-> list x 
-> pq (list (K Result ys)) 

forPrepared Source #

Arguments

:: (ToParams x params, Traversable list) 
=> list x 
-> Manipulation schema params ys

insertRows, update or deleteFrom

-> pq (list (K Result ys)) 

traversePrepared_ Source #

Arguments

:: (ToParams x params, Foldable list) 
=> Manipulation schema params '[]

insertRows, update or deleteFrom

-> list x 
-> pq () 

traversePrepared_ Source #

Arguments

:: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) 
=> (ToParams x params, Foldable list) 
=> Manipulation schema params '[]

insertRows, update or deleteFrom

-> list x 
-> pq () 

forPrepared_ Source #

Arguments

:: (ToParams x params, Foldable list) 
=> list x 
-> Manipulation schema params '[]

insertRows, update or deleteFrom

-> pq () 

liftPQ :: (Connection -> IO a) -> pq a Source #

liftPQ :: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) => (Connection -> IO a) -> pq a Source #

Instances

MonadPQ schema m => MonadPQ schema (ListT m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> ListT m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> ListT m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> ListT m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> ListT m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> ListT m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> ListT m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> ListT m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> ListT m () Source #

liftPQ :: (Connection -> IO a) -> ListT m a Source #

MonadPQ schema m => MonadPQ schema (MaybeT m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> MaybeT m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> MaybeT m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> MaybeT m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> MaybeT m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> MaybeT m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> MaybeT m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> MaybeT m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> MaybeT m () Source #

liftPQ :: (Connection -> IO a) -> MaybeT m a Source #

MonadPQ schema m => MonadPQ schema (ExceptT e m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> ExceptT e m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> ExceptT e m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> ExceptT e m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> ExceptT e m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> ExceptT e m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> ExceptT e m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> ExceptT e m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> ExceptT e m () Source #

liftPQ :: (Connection -> IO a) -> ExceptT e m a Source #

(Monoid w, MonadPQ schema m) => MonadPQ schema (WriterT w m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> WriterT w m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> WriterT w m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> WriterT w m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> WriterT w m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> WriterT w m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> WriterT w m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> WriterT w m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> WriterT w m () Source #

liftPQ :: (Connection -> IO a) -> WriterT w m a Source #

(Monoid w, MonadPQ schema m) => MonadPQ schema (WriterT w m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> WriterT w m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> WriterT w m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> WriterT w m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> WriterT w m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> WriterT w m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> WriterT w m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> WriterT w m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> WriterT w m () Source #

liftPQ :: (Connection -> IO a) -> WriterT w m a Source #

MonadPQ schema m => MonadPQ schema (StateT s m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> StateT s m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> StateT s m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> StateT s m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> StateT s m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> StateT s m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> StateT s m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> StateT s m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> StateT s m () Source #

liftPQ :: (Connection -> IO a) -> StateT s m a Source #

MonadPQ schema m => MonadPQ schema (StateT s m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> StateT s m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> StateT s m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> StateT s m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> StateT s m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> StateT s m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> StateT s m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> StateT s m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> StateT s m () Source #

liftPQ :: (Connection -> IO a) -> StateT s m a Source #

MonadPQ schema m => MonadPQ schema (IdentityT * m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> IdentityT * m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> IdentityT * m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> IdentityT * m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> IdentityT * m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> IdentityT * m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> IdentityT * m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> IdentityT * m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> IdentityT * m () Source #

liftPQ :: (Connection -> IO a) -> IdentityT * m a Source #

MonadPQ schema m => MonadPQ schema (ContT * r m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> ContT * r m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> ContT * r m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> ContT * r m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> ContT * r m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> ContT * r m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> ContT * r m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> ContT * r m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> ContT * r m () Source #

liftPQ :: (Connection -> IO a) -> ContT * r m a Source #

MonadPQ schema m => MonadPQ schema (ReaderT * r m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> ReaderT * r m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> ReaderT * r m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> ReaderT * r m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> ReaderT * r m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> ReaderT * r m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> ReaderT * r m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> ReaderT * r m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> ReaderT * r m () Source #

liftPQ :: (Connection -> IO a) -> ReaderT * r m a Source #

(MonadBase IO io, (~) TablesType schema0 schema, (~) TablesType schema1 schema) => MonadPQ schema (PQ schema0 schema1 io) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> PQ schema0 schema1 io (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> PQ schema0 schema1 io (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> PQ schema0 schema1 io (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> PQ schema0 schema1 io (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> PQ schema0 schema1 io (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> PQ schema0 schema1 io (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> PQ schema0 schema1 io () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> PQ schema0 schema1 io () Source #

liftPQ :: (Connection -> IO a) -> PQ schema0 schema1 io a Source #

MonadBaseControl IO io => MonadPQ schema (PoolPQ * schema io) Source #

MonadPQ instance for PoolPQ.

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> PoolPQ * schema io (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> PoolPQ * schema io (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> PoolPQ * schema io (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> PoolPQ * schema io (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> PoolPQ * schema io (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> PoolPQ * schema io (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> PoolPQ * schema io () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> PoolPQ * schema io () Source #

liftPQ :: (Connection -> IO a) -> PoolPQ * schema io a Source #

(Monoid w, MonadPQ schema m) => MonadPQ schema (RWST r w s m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> RWST r w s m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> RWST r w s m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> RWST r w s m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> RWST r w s m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> RWST r w s m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> RWST r w s m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> RWST r w s m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> RWST r w s m () Source #

liftPQ :: (Connection -> IO a) -> RWST r w s m a Source #

(Monoid w, MonadPQ schema m) => MonadPQ schema (RWST r w s m) Source # 

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> RWST r w s m (K RelationType Result ys) Source #

manipulate :: Manipulation schema [NullityType] ys -> RWST r w s m (K RelationType Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> RWST r w s m (K RelationType Result ys) Source #

runQuery :: Query schema [NullityType] ys -> RWST r w s m (K RelationType Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> RWST r w s m (list (K RelationType Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> RWST r w s m (list (K RelationType Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [(Symbol, NullityType)] -> list x -> RWST r w s m () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, NullityType)] -> RWST r w s m () Source #

liftPQ :: (Connection -> IO a) -> RWST r w s m a Source #

type PQRun schema = forall m x. Monad m => PQ schema schema m x -> m (K x schema) Source #

A snapshot of the state of a PQ computation.

pqliftWith :: Functor m => (PQRun schema -> m a) -> PQ schema schema m a Source #

Helper function in defining MonadBaseControl instance for PQ.

Result

data Result :: * #

Result encapsulates the result of a query (or more precisely, of a single SQL command --- a query string given to sendQuery can contain multiple commands and thus return multiple instances of Result.

Instances

Eq Result 

Methods

(==) :: Result -> Result -> Bool #

(/=) :: Result -> Result -> Bool #

Show Result 

data Row :: * #

Instances

Enum Row 

Methods

succ :: Row -> Row #

pred :: Row -> Row #

toEnum :: Int -> Row #

fromEnum :: Row -> Int #

enumFrom :: Row -> [Row] #

enumFromThen :: Row -> Row -> [Row] #

enumFromTo :: Row -> Row -> [Row] #

enumFromThenTo :: Row -> Row -> Row -> [Row] #

Eq Row 

Methods

(==) :: Row -> Row -> Bool #

(/=) :: Row -> Row -> Bool #

Num Row 

Methods

(+) :: Row -> Row -> Row #

(-) :: Row -> Row -> Row #

(*) :: Row -> Row -> Row #

negate :: Row -> Row #

abs :: Row -> Row #

signum :: Row -> Row #

fromInteger :: Integer -> Row #

Ord Row 

Methods

compare :: Row -> Row -> Ordering #

(<) :: Row -> Row -> Bool #

(<=) :: Row -> Row -> Bool #

(>) :: Row -> Row -> Bool #

(>=) :: Row -> Row -> Bool #

max :: Row -> Row -> Row #

min :: Row -> Row -> Row #

Show Row 

Methods

showsPrec :: Int -> Row -> ShowS #

show :: Row -> String #

showList :: [Row] -> ShowS #

ntuples :: MonadBase IO io => K Result columns -> io Row Source #

Returns the number of rows (tuples) in the query result.

getRow Source #

Arguments

:: (FromRow columns y, MonadBase IO io) 
=> Row

row number

-> K Result columns

result

-> io y 

Get a row corresponding to a given row number from a Result, throwing an exception if the row number is out of bounds.

getRows Source #

Arguments

:: (FromRow columns y, MonadBase IO io) 
=> K Result columns

result

-> io [y] 

Get all rows from a Result.

nextRow Source #

Arguments

:: (FromRow columns y, MonadBase IO io) 
=> Row

total number of rows

-> K Result columns

result

-> Row

row number

-> io (Maybe (Row, y)) 

Intended to be used for unfolding in streaming libraries, nextRow takes a total number of rows (which can be found with ntuples) and a Result and given a row number if it's too large returns Nothing, otherwise returning the row along with the next row number.

firstRow Source #

Arguments

:: (FromRow columns y, MonadBase IO io) 
=> K Result columns

result

-> io (Maybe y) 

Get the first row if possible from a Result.

liftResult :: MonadBase IO io => (Result -> IO x) -> K Result results -> io x Source #

Lifts actions on results from LibPQ.

data ExecStatus :: * #

Constructors

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.

resultStatus :: MonadBase IO io => K Result results -> io ExecStatus Source #

Returns the result status of the command.

resultErrorMessage :: MonadBase IO io => K Result results -> io (Maybe ByteString) Source #

Returns the error message most recently generated by an operation on the connection.