Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hasql
Contents
Description
This is the API of the "hasql" library. For an introduction to the package and links to more documentation please refer to the package's index page.
This API is completely disinfected from exceptions.
All error-reporting is explicit and
is presented using the Either
type.
- data Pool c
- acquirePool :: Cx c => CxSettings c -> PoolSettings -> IO (Pool c)
- releasePool :: Pool c -> IO ()
- data PoolSettings
- poolSettings :: Int -> Int -> Maybe PoolSettings
- data Session c m r
- session :: Pool c -> Session c m a -> m (Either (SessionError c) a)
- data SessionError c
- data Stmt c :: * -> *
- stmt :: QuasiQuoter
- unitTx :: Stmt c -> Tx c s ()
- countTx :: CxValue c Word64 => Stmt c -> Tx c s Word64
- singleTx :: RowParser c r => Stmt c -> Tx c s r
- maybeTx :: RowParser c r => Stmt c -> Tx c s (Maybe r)
- listTx :: RowParser c r => Stmt c -> Tx c s [r]
- vectorTx :: RowParser c r => Stmt c -> Tx c s (Vector r)
- streamTx :: RowParser c r => Stmt c -> Tx c s (TxListT s (Tx c s) r)
- data Tx c s r
- tx :: (CxTx c, MonadBaseControl IO m) => TxMode -> (forall s. Tx c s r) -> Session c m r
- type TxMode = Maybe (TxIsolationLevel, TxWriteMode)
- data TxIsolationLevel :: *
- type TxWriteMode = Maybe Bool
- data TxListT s m r
- class RowParser c r
Pool
acquirePool :: Cx c => CxSettings c -> PoolSettings -> IO (Pool c) Source
Given backend-specific connection settings and pool settings, acquire a backend connection pool, which can then be used to work with the DB.
When combining Hasql with other libraries,
which throw exceptions it makes sence to utilize
Control.Exception.
like this:bracket
bracket (acquirePool bkndStngs poolStngs) (releasePool) $ \pool -> do session pool $ do ... ... any other IO code
releasePool :: Pool c -> IO () Source
Release all connections acquired by the pool.
Pool Settings
data PoolSettings Source
Settings of a pool.
Arguments
:: Int | The maximum number of connections to keep open. The smallest acceptable value is 1. Requests for connections will block if this limit is reached. |
-> Int | The amount of seconds for which an unused connection is kept open. The smallest acceptable value is 1. |
-> Maybe PoolSettings | Maybe pool settings, if they are correct. |
A smart constructor for pool settings.
Session
A convenience wrapper around ReaderT
,
which provides a shared context for execution and error-handling of transactions.
Instances
MonadBase IO m => MonadBase IO (Session c m) | |
MonadBaseControl IO m => MonadBaseControl IO (Session c m) | |
MonadTrans (Session c) | |
MFunctor (Session c) | |
MonadTransControl (Session c) | |
Monad m => MonadError (SessionError c) (Session c m) | |
Monad m => Monad (Session c m) | |
Monad m => Functor (Session c m) | |
Monad m => Applicative (Session c m) | |
MonadIO m => MonadIO (Session c m) | |
type StT (Session c) a = Either (SessionError c) a | |
type StM (Session c m) a = ComposeSt (Session c) m a |
session :: Pool c -> Session c m a -> m (Either (SessionError c) a) Source
Execute a session using an established connection pool.
This is merely a wrapper around runReaderT
,
so you can run it around every transaction,
if you want.
Session Error
data SessionError c Source
Constructors
CxError (CxError c) | A backend-specific connection acquisition error. E.g., a failure to establish a connection. |
TxError (TxError c) | A backend-specific transaction error. It should cover all possible failures related to an established connection, including the loss of connection, query errors and database failures. |
ResultError Text | Attempt to parse a result into an incompatible type. Indicates either a mismatching schema or an incorrect query. |
Instances
(Eq (CxError c), Eq (TxError c)) => Eq (SessionError c) | |
(Show (CxError c), Show (TxError c)) => Show (SessionError c) | |
Monad m => MonadError (SessionError c) (Session c m) |
Statement
data Stmt c :: * -> *
A statement template packed with its values and settings.
Produces a lambda-expression,
which takes as many parameters as there are placeholders in the quoted text
and results in a Stmt
.
E.g.:
selectSum :: Int -> Int -> Stmt c selectSum = [stmt|SELECT (? + ?)|]
Statement Execution
countTx :: CxValue c Word64 => Stmt c -> Tx c s Word64 Source
Execute a statement and count the amount of affected rows. Useful for resolving how many rows were updated or deleted.
singleTx :: RowParser c r => Stmt c -> Tx c s r Source
Execute a statement,
which produces exactly one result row.
E.g., INSERT
, which returns an autoincremented identifier,
or SELECT COUNT
, or SELECT EXISTS
.
Please note that using this executor for selecting rows is conceptually wrong,
since in that case the results are always optional.
Use maybeTx
, listTx
or vectorTx
instead.
If the result is empty this executor will raise ResultError
.
maybeTx :: RowParser c r => Stmt c -> Tx c s (Maybe r) Source
Execute a statement, which optionally produces a single result row.
listTx :: RowParser c r => Stmt c -> Tx c s [r] Source
Execute a statement, and produce a list of results.
vectorTx :: RowParser c r => Stmt c -> Tx c s (Vector r) Source
Execute a statement, and produce a vector of results.
streamTx :: RowParser c r => Stmt c -> Tx c s (TxListT s (Tx c s) r) Source
Execute a SELECT
statement with a cursor,
and produce a result stream.
Cursor allows you to fetch virtually limitless results in a constant memory at a cost of a small overhead. Note that in most databases cursors require establishing a database transaction, so depending on a backend the transaction may result in an error, if you run it improperly.
Transaction
A transaction specialized for a backend connection c
,
associated with its intermediate results using an anonymous type-argument s
(same trick as in ST
)
and producing a result r
.
Running IO
in Tx
is prohibited.
The motivation is identical to STM
:
the Tx
block may get executed multiple times if any transaction conflicts arise.
This will result in your effectful IO
code being executed
an unpredictable amount of times as well,
which, chances are, is not what you want.
tx :: (CxTx c, MonadBaseControl IO m) => TxMode -> (forall s. Tx c s r) -> Session c m r Source
Execute a transaction in a session.
This function ensures on the type level,
that it's impossible to return
from it.TxListT
s m r
Transaction Settings
type TxMode = Maybe (TxIsolationLevel, TxWriteMode)
A mode, defining how a transaction should be executed.
Just (isolationLevel, write)
indicates that a database transaction should be established with a specified isolation level and a write mode.Nothing
indicates that there should be no database transaction established on the backend and therefore it should be executed with no ACID guarantees, but also without any induced overhead.
data TxIsolationLevel :: *
For reference see the Wikipedia info.
Constructors
RepeatableReads | |
Serializable | |
ReadCommitted | |
ReadUncommitted |
type TxWriteMode = Maybe Bool
Nothing
indicates a "read" mode.Just True
indicates a "write" mode.Just False
indicates a "write" mode without committing. This is useful for testing, allowing you to modify your database, producing some result based on your changes, and to let Hasql roll all the changes back on the exit from the transaction.
Result Stream
A stream of results, which fetches only those that you reach.
It's a wrapper around ListT
,
which uses the same trick as the ST
monad to associate with the
context transaction and become impossible to be used outside of it.
This lets the library ensure that it is safe to automatically
release all the connections associated with this stream.
All the functions of the "list-t" library are applicable to this type,
amongst which are head
, toList
, fold
, traverse_
.
Instances
MonadTrans (TxListT s) | |
MonadTransUncons (TxListT s) | |
(Monad m, Functor m) => Alternative (TxListT s m) | |
Monad m => Monad (TxListT s m) | |
Functor m => Functor (TxListT s m) | |
Monad m => MonadPlus (TxListT s m) | |
(Monad m, Functor m) => Applicative (TxListT s m) | |
Monad m => MonadCons (TxListT s m) | |
Monad m => Monoid (TxListT s m r) |
Row Parser
This class is only intended to be used with the supplied instances, which should be enough to cover all use cases.
Minimal complete definition
parseRow
Instances
RowParser c () | |
CxValue c v => RowParser c (Identity v) | |
(CxValue c v1, CxValue c v2) => RowParser c (v1, v2) | |
(CxValue c v1, CxValue c v2, CxValue c v3) => RowParser c (v1, v2, v3) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4) => RowParser c (v1, v2, v3, v4) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5) => RowParser c (v1, v2, v3, v4, v5) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6) => RowParser c (v1, v2, v3, v4, v5, v6) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7) => RowParser c (v1, v2, v3, v4, v5, v6, v7) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18, CxValue c v19) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18, v19) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18, CxValue c v19, CxValue c v20) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18, v19, v20) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18, CxValue c v19, CxValue c v20, CxValue c v21) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18, v19, v20, v21) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18, CxValue c v19, CxValue c v20, CxValue c v21, CxValue c v22) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18, v19, v20, v21, v22) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18, CxValue c v19, CxValue c v20, CxValue c v21, CxValue c v22, CxValue c v23) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18, v19, v20, v21, v22, v23) | |
(CxValue c v1, CxValue c v2, CxValue c v3, CxValue c v4, CxValue c v5, CxValue c v6, CxValue c v7, CxValue c v8, CxValue c v9, CxValue c v10, CxValue c v11, CxValue c v12, CxValue c v13, CxValue c v14, CxValue c v15, CxValue c v16, CxValue c v17, CxValue c v18, CxValue c v19, CxValue c v20, CxValue c v21, CxValue c v22, CxValue c v23, CxValue c v24) => RowParser c (v1, v2, v3, v4, v5, v6, v7, v8, v9, v10, v11, v12, v13, v14, v15, v16, v17, v18, v19, v20, v21, v22, v23, v24) |