Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype DBT m a = DBT {
- unDBT :: ReaderT Connection m a
- type DB = DBT IO
- isClass25 :: SqlError -> Bool
- isNoTransaction :: SqlError -> Bool
- getConnection :: Monad m => DBT m Connection
- runDBT :: MonadBaseControl IO m => DBT m a -> IsolationLevel -> Connection -> m a
- runDBTSerializable :: MonadBaseControl IO m => DBT m a -> Connection -> m a
- runDBTNoTransaction :: DBT m a -> Connection -> m a
- query :: (ToRow a, FromRow b, MonadIO m) => Query -> a -> DBT m [b]
- query_ :: (FromRow b, MonadIO m) => Query -> DBT m [b]
- execute :: (ToRow q, MonadIO m) => Query -> q -> DBT m Int64
- execute_ :: MonadIO m => Query -> DBT m Int64
- executeMany :: (ToRow q, MonadIO m) => Query -> [q] -> DBT m Int64
- returning :: (ToRow q, FromRow r, MonadIO m) => Query -> [q] -> DBT m [r]
- formatQuery :: (ToRow q, MonadIO m) => Query -> q -> DBT m ByteString
- queryOne :: (MonadIO m, ToRow a, FromRow b) => Query -> a -> DBT m (Maybe b)
- queryOne_ :: (MonadIO m, FromRow b) => Query -> DBT m (Maybe b)
- savepoint :: MonadIO m => DBT m Savepoint
- rollbackToAndReleaseSavepoint :: MonadIO m => Savepoint -> DBT m ()
- rollback :: (MonadMask m, MonadIO m) => DBT m a -> DBT m a
- data Abort = Abort
- abort :: (MonadMask m, MonadIO m) => DBT m a -> DBT m a
Documentation
DBT | |
|
Instances
MonadTrans DBT Source # | |
Defined in Database.PostgreSQL.Transact | |
Monad m => Monad (DBT m) Source # | |
Functor m => Functor (DBT m) Source # | |
MonadFail m => MonadFail (DBT m) Source # | |
Defined in Database.PostgreSQL.Transact | |
Applicative m => Applicative (DBT m) Source # | |
MonadIO m => MonadIO (DBT m) Source # | |
Defined in Database.PostgreSQL.Transact | |
MonadThrow m => MonadThrow (DBT m) Source # | |
Defined in Database.PostgreSQL.Transact | |
(MonadIO m, MonadMask m) => MonadCatch (DBT m) Source # | |
(MonadIO m, MonadMask m) => MonadMask (DBT m) Source # | |
(Applicative m, Semigroup a) => Semigroup (DBT m a) Source # | |
(Applicative m, Monoid a) => Monoid (DBT m a) Source # | |
isNoTransaction :: SqlError -> Bool Source #
getConnection :: Monad m => DBT m Connection Source #
runDBT :: MonadBaseControl IO m => DBT m a -> IsolationLevel -> Connection -> m a Source #
runDBTSerializable :: MonadBaseControl IO m => DBT m a -> Connection -> m a Source #
runDBTNoTransaction :: DBT m a -> Connection -> m a Source #
query :: (ToRow a, FromRow b, MonadIO m) => Query -> a -> DBT m [b] Source #
Perform a SELECT
or other SQL query that is expected to return
results. All results are retrieved and converted before this
function returns.
When processing large results, this function will consume a lot of
client-side memory. Consider using fold
instead.
Exceptions that may be thrown:
FormatError
: the query string could not be formatted correctly.QueryError
: the result contains no columns (i.e. you should be usingexecute
instead ofquery
).ResultError
: result conversion failed.SqlError
: the postgresql backend returned an error, e.g. a syntax or type error, or an incorrect table or column name.
query_ :: (FromRow b, MonadIO m) => Query -> DBT m [b] Source #
A version of query
that does not perform query substitution.
execute :: (ToRow q, MonadIO m) => Query -> q -> DBT m Int64 Source #
Execute an INSERT
, UPDATE
, or other SQL query that is not
expected to return results.
Returns the number of rows affected.
Throws FormatError
if the query could not be formatted correctly, or
a SqlError
exception if the backend returns an error.
execute_ :: MonadIO m => Query -> DBT m Int64 Source #
A version of execute that does not perform query substitution.
executeMany :: (ToRow q, MonadIO m) => Query -> [q] -> DBT m Int64 Source #
Execute a multi-row INSERT
, UPDATE
, or other SQL query that is not
expected to return results.
Returns the number of rows affected. If the list of parameters is empty,
this function will simply return 0 without issuing the query to the backend.
If this is not desired, consider using the Values
constructor instead.
Throws FormatError
if the query could not be formatted correctly, or
a SqlError
exception if the backend returns an error.
For example, here's a command that inserts two rows into a table with two columns:
executeMany [sql| INSERT INTO sometable VALUES (?,?) |] [(1, "hello"),(2, "world")]
Here's an canonical example of a multi-row update command:
executeMany [sql| UPDATE sometable SET sometable.y = upd.y FROM (VALUES (?,?)) as upd(x,y) WHERE sometable.x = upd.x |] [(1, "hello"),(2, "world")]
returning :: (ToRow q, FromRow r, MonadIO m) => Query -> [q] -> DBT m [r] Source #
Execute INSERT ... RETURNING
, UPDATE ... RETURNING
, or other SQL
query that accepts multi-row input and is expected to return results.
Note that it is possible to write
in cases where you are only inserting a single row, and do not need
functionality analogous to query
conn "INSERT ... RETURNING ..." ...executeMany
.
If the list of parameters is empty, this function will simply return []
without issuing the query to the backend. If this is not desired,
consider using the Values
constructor instead.
Throws FormatError
if the query could not be formatted correctly.
formatQuery :: (ToRow q, MonadIO m) => Query -> q -> DBT m ByteString Source #
Format a query string.
This function is exposed to help with debugging and logging. Do not use it to prepare queries for execution.
String parameters are escaped according to the character set in use
on the Connection
.
Throws FormatError
if the query string could not be formatted
correctly.
rollbackToAndReleaseSavepoint :: MonadIO m => Savepoint -> DBT m () Source #
Release the Savepoint
and discard the effects.
rollback :: (MonadMask m, MonadIO m) => DBT m a -> DBT m a Source #
Run an action and discard the effects but return the result
Instances
Eq Abort Source # | |
Show Abort Source # | |
Exception Abort Source # | |
Defined in Database.PostgreSQL.Transact toException :: Abort -> SomeException # fromException :: SomeException -> Maybe Abort # displayException :: Abort -> String # |
abort :: (MonadMask m, MonadIO m) => DBT m a -> DBT m a Source #
A abort
is a similar to rollback
but calls ROLLBACK
to abort the
transaction. abort
s is global. It affects everything before and after
it is called. Duplicate abort
s do nothing.
Calling abort
throws an Abort
exception that is not caught
by the transaction running functions. If you call abort
you need to
also be prepared to handle the Abort
exception.