| Copyright | (c) Eitan Chatav 2017 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
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.
- data Connection (schema :: TablesType)
- connectdb :: forall schema io. MonadBase IO io => ByteString -> io (Connection schema)
- finish :: MonadBase IO io => Connection schema -> io ()
- withConnection :: forall schema io x. MonadBaseControl IO io => ByteString -> (Connection schema -> io x) -> io x
- data PQ (schema0 :: TablesType) (schema1 :: TablesType) (m :: Type -> Type) (x :: Type)
- execPQ :: Functor m => PQ schema0 schema1 m x -> Connection schema0 -> m (Connection schema1)
- pqAp :: Monad m => PQ schema0 schema1 m (x -> y) -> PQ schema1 schema2 m x -> PQ schema0 schema2 m y
- pqBind :: Monad m => (x -> PQ schema1 schema2 m y) -> PQ schema0 schema1 m x -> PQ schema0 schema2 m y
- pqThen :: Monad m => PQ schema1 schema2 m y -> PQ schema0 schema1 m x -> PQ schema0 schema2 m y
- define :: MonadBase IO io => Definition schema0 schema1 -> PQ schema0 schema1 io (Result '[])
- thenDefine :: MonadBase IO io => Definition schema1 schema2 -> PQ schema0 schema1 io x -> PQ schema0 schema2 io (Result '[])
- class Monad pq => MonadPQ schema pq | pq -> schema where
- type PQRun schema = forall m x. Monad m => PQ schema schema m x -> m (x, Connection schema)
- pqliftWith :: Functor m => (PQRun schema -> m a) -> PQ schema schema m a
- newtype Result (columns :: ColumnsType) = Result {}
- newtype RowNumber = RowNumber {
- unRowNumber :: Row
- newtype ColumnNumber (n :: Nat) (cs :: [k]) (c :: k) = UnsafeColumnNumber {}
- class KnownNat n => HasColumnNumber n columns column | n columns -> column where
- getValue :: (FromColumnValue colty y, MonadBase IO io) => RowNumber -> ColumnNumber n columns colty -> Result columns -> io y
- getRow :: (FromRow columns y, MonadBase IO io) => RowNumber -> Result columns -> io y
- getRows :: (FromRow columns y, MonadBase IO io) => Result columns -> io [y]
- ntuples :: MonadBase IO io => Result columns -> io RowNumber
- nextRow :: (FromRow columns y, MonadBase IO io) => RowNumber -> Result columns -> RowNumber -> io (Maybe (RowNumber, y))
- firstRow :: (FromRow columns y, MonadBase IO io) => Result columns -> io (Maybe y)
- liftResult :: MonadBase IO io => (Result -> IO x) -> Result results -> io x
Connection
data Connection (schema :: TablesType) Source #
A Connection consists of a LibPQ
Connection and a phantom TablesType
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 schema io x. MonadBaseControl IO io => ByteString -> (Connection schema -> io x) -> io x Source #
PQ
data 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.
Instances
| MonadBase b m => MonadBase b (PQ schema schema m) Source # | |
| MonadBaseControl b m => MonadBaseControl b (PQ schema schema m) Source # | |
| MonadBase IO io => MonadPQ schema (PQ schema schema io) Source # | |
| MonadTrans (PQ schema schema) Source # | |
| Monad m => Monad (PQ schema schema m) Source # | |
| Functor m => Functor (PQ schema0 schema1 m) Source # | |
| Monad m => Applicative (PQ schema schema m) Source # | |
| type StM (PQ schema schema m) x Source # | |
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
pqThen (define statement2) statement1 = define (statement2 . statement1)
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
manipulateParamsruns aManipulationwith params from a type with aToParamsconstraint. It callsexecParamsand doesn't afraid of anything.manipulateis likemanipulateParamsfor a parameter-free statement.runQueryParamsis likemanipulateParamsfor query statements.traversePreparedhas the same type signature as a composition oftraverseandmanipulateParamsbut provides an optimization by preparing the statement withprepareand then traversing aTraversablecontainer withexecPrepared. The temporary prepared statement is then deallocated.forPreparedis a flippedtraversePreparedtraversePrepared_is liketraversePreparedbut works onFoldablecontainers and returns unit.forPrepared_is a flippedtraversePrepared_.liftPQlets you lift actions fromLibPQthat 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.
Methods
Arguments
| :: ToParams x params | |
| => Manipulation schema params ys | |
| -> x | |
| -> pq (Result ys) |
Arguments
| :: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) | |
| => ToParams x params | |
| => Manipulation schema params ys | |
| -> x | |
| -> pq (Result ys) |
manipulate :: Manipulation schema '[] ys -> pq (Result ys) Source #
Arguments
| :: (ToParams x params, Traversable list) | |
| => Manipulation schema params ys | |
| -> list x | |
| -> pq (list (Result ys)) |
Arguments
| :: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) | |
| => (ToParams x params, Traversable list) | |
| => Manipulation schema params ys | |
| -> list x | |
| -> pq (list (Result ys)) |
Arguments
| :: (ToParams x params, Traversable list) | |
| => list x | |
| -> Manipulation schema params ys | |
| -> pq (list (Result ys)) |
Arguments
| :: (ToParams x params, Foldable list) | |
| => Manipulation schema params '[] | |
| -> list x | |
| -> pq () |
Arguments
| :: (MonadTrans t, MonadPQ schema pq1, pq ~ t pq1) | |
| => (ToParams x params, Foldable list) | |
| => Manipulation schema params '[] | |
| -> list x | |
| -> pq () |
Arguments
| :: (ToParams x params, Traversable list) | |
| => list x | |
| -> Manipulation schema params '[] | |
| -> 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 # | |
| MonadPQ schema m => MonadPQ schema (MaybeT m) Source # | |
| MonadPQ schema m => MonadPQ schema (ExceptT e m) Source # | |
| (Monoid w, MonadPQ schema m) => MonadPQ schema (WriterT w m) Source # | |
| (Monoid w, MonadPQ schema m) => MonadPQ schema (WriterT w m) Source # | |
| MonadPQ schema m => MonadPQ schema (StateT s m) Source # | |
| MonadPQ schema m => MonadPQ schema (StateT s m) Source # | |
| MonadPQ schema m => MonadPQ schema (IdentityT * m) Source # | |
| MonadPQ schema m => MonadPQ schema (ContT * r m) Source # | |
| MonadPQ schema m => MonadPQ schema (ReaderT * r m) Source # | |
| MonadBase IO io => MonadPQ schema (PQ schema schema io) Source # | |
| (Monoid w, MonadPQ schema m) => MonadPQ schema (RWST r w s m) Source # | |
| (Monoid w, MonadPQ schema m) => MonadPQ schema (RWST r w s m) 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.
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 | |
Fields | |
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 # | |
| HasColumnNumber k 0 ((:) k column1 columns) column1 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.
Get a row corresponding to a given row number from a Result.
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.
Get the first row if possible from a Result.