squeal-postgresql-0.1.1.4: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.PQ

Contents

Description

PQ is where Squeal statements come to actually get run by LibPQ. It contains a PQ indexed monad transformer to run Definitions and a MonadPQ constraint for running a Manipulation or Query.

Synopsis

Connection

newtype Connection (schema :: TablesType) Source #

A Connection consists of a LibPQ Connection and a phantom TablesType

Constructors

Connection 

connectdb Source #

Arguments

:: MonadBase IO io 
=> ByteString

conninfo

-> io (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 -XTypeOperators
>>> type Schema = '["tab" ::: '["col" ::: 'Required ('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 => Connection schema -> io () Source #

Closes the connection to the server.

withConnection :: forall schema0 schema1 io x. MonadBaseControl IO io => ByteString -> (Connection schema0 -> io (x, Connection schema1)) -> io x Source #

Do connectdb and finish before and after a computation.

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

MonadBase b m => MonadBase b (PQ schema schema m) Source # 

Methods

liftBase :: b α -> PQ schema schema m α #

MonadBaseControl b m => MonadBaseControl b (PQ schema schema m) Source # 

Associated Types

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

Methods

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

restoreM :: StM (PQ schema schema m) a -> PQ schema schema m a #

MonadBase IO io => MonadPQ schema (PQ schema schema io) Source # 

Methods

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

manipulate :: Manipulation schema [ColumnType] ys -> PQ schema schema io (Result ys) Source #

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

runQuery :: Query schema [ColumnType] ys -> PQ schema schema io (Result ys) Source #

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

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

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

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

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

MonadTrans (PQ schema schema) Source # 

Methods

lift :: Monad m => m a -> PQ schema schema m a #

Monad m => Monad (PQ schema schema m) Source # 

Methods

(>>=) :: PQ schema schema m a -> (a -> PQ schema schema m b) -> PQ schema schema m b #

(>>) :: PQ schema schema m a -> PQ schema schema m b -> PQ schema schema m b #

return :: a -> PQ schema schema m a #

fail :: String -> PQ schema schema m a #

Functor 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 => Applicative (PQ schema schema m) Source # 

Methods

pure :: a -> PQ schema schema m a #

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

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

(*>) :: PQ schema schema m a -> PQ schema schema m b -> PQ schema schema m b #

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

type StM (PQ schema schema m) x Source # 
type StM (PQ schema schema m) x = StM m (x, Connection schema)

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

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

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

indexed analog of <*>

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 >>

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

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

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

thenDefine :: MonadBase IO io => Definition schema1 schema2 -> PQ schema0 schema1 io x -> PQ schema0 schema2 io (Result '[]) Source #

Chain together define actions.

MonadPQ

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

insertInto, update or deleteFrom

-> x 
-> pq (Result ys) 

manipulateParams Source #

Arguments

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

insertInto, update or deleteFrom

-> x 
-> pq (Result ys) 

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

runQueryParams Source #

Arguments

:: ToParams x params 
=> Query schema params ys

select and friends

-> x 
-> pq (Result ys) 

runQuery Source #

Arguments

:: Query schema '[] ys

select and friends

-> pq (Result ys) 

traversePrepared Source #

Arguments

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

insertInto, update or deleteFrom

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

traversePrepared Source #

Arguments

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

insertInto, update or deleteFrom

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

forPrepared Source #

Arguments

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

insertInto, update or deleteFrom

-> pq (list (Result ys)) 

traversePrepared_ Source #

Arguments

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

insertInto, 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 '[]

insertInto, update or deleteFrom

-> list x 
-> pq () 

forPrepared_ Source #

Arguments

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

insertInto, 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

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

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

MonadBase IO io => MonadPQ schema (PQ schema schema io) Source # 

Methods

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

manipulate :: Manipulation schema [ColumnType] ys -> PQ schema schema io (Result ys) Source #

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

runQuery :: Query schema [ColumnType] ys -> PQ schema schema io (Result ys) Source #

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

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

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

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

liftPQ :: (Connection -> IO a) -> PQ schema 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (Result ys) Source #

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

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

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

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

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

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

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [(Symbol, ColumnType)] -> 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 (x, Connection 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

newtype Result (columns :: ColumnsType) Source #

Encapsulates the result of a squeal command run by LibPQ. Results are parameterized by a ColumnsType describing the column names and their types.

Constructors

Result 

Fields

newtype RowNumber Source #

Just newtypes around a CInt

Constructors

RowNumber 

Fields

newtype ColumnNumber (n :: Nat) (cs :: [k]) (c :: k) Source #

In addition to being newtypes around a CInt, a ColumnNumber is parameterized by a Natural number and acts as an index into a row.

Constructors

UnsafeColumnNumber 

class KnownNat n => HasColumnNumber n columns column | n columns -> column where Source #

>>> getColumnNumber (columnNumber @5 @'[_,_,_,_,_,_])
Col 5

Methods

columnNumber :: ColumnNumber n columns column Source #

Instances

(KnownNat n, HasColumnNumber k ((-) n 1) columns column) => HasColumnNumber k n ((:) k column' columns) column Source # 

Methods

columnNumber :: ColumnNumber n ((k ': column') columns) column column Source #

HasColumnNumber k 0 ((:) k column1 columns) column1 Source # 

Methods

columnNumber :: ColumnNumber 0 ((k ': column1) columns) column1 column Source #

getValue Source #

Arguments

:: (FromColumnValue colty y, MonadBase IO io) 
=> RowNumber

row

-> ColumnNumber n columns colty

col

-> Result columns

result

-> io y 

Get a single value corresponding to a given row and column number from a Result.

getRow Source #

Arguments

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

row

-> Result columns

result

-> io y 

Get a row corresponding to a given row number from a Result.

getRows Source #

Arguments

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

result

-> io [y] 

Get all rows from a Result.

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

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

nextRow Source #

Arguments

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

total number of rows

-> Result columns

result

-> RowNumber

row number

-> io (Maybe (RowNumber, 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) 
=> Result columns

result

-> io (Maybe y) 

Get the first row if possible from a Result.

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

Lifts actions on results from LibPQ.