pg-transact-0.3.2.0: A postgresql-simple transaction monad
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Transact

Synopsis

Documentation

newtype DBT m a Source #

Constructors

DBT 

Fields

Instances

Instances details
MonadTrans DBT Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

lift :: Monad m => m a -> DBT m a #

Monad m => Monad (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

(>>=) :: DBT m a -> (a -> DBT m b) -> DBT m b #

(>>) :: DBT m a -> DBT m b -> DBT m b #

return :: a -> DBT m a #

Functor m => Functor (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

fmap :: (a -> b) -> DBT m a -> DBT m b #

(<$) :: a -> DBT m b -> DBT m a #

MonadFail m => MonadFail (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

fail :: String -> DBT m a #

Applicative m => Applicative (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

pure :: a -> DBT m a #

(<*>) :: DBT m (a -> b) -> DBT m a -> DBT m b #

liftA2 :: (a -> b -> c) -> DBT m a -> DBT m b -> DBT m c #

(*>) :: DBT m a -> DBT m b -> DBT m b #

(<*) :: DBT m a -> DBT m b -> DBT m a #

MonadIO m => MonadIO (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

liftIO :: IO a -> DBT m a #

MonadThrow m => MonadThrow (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

throwM :: Exception e => e -> DBT m a #

(MonadIO m, MonadMask m) => MonadCatch (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

catch :: Exception e => DBT m a -> (e -> DBT m a) -> DBT m a #

(MonadIO m, MonadMask m) => MonadMask (DBT m) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

mask :: ((forall a. DBT m a -> DBT m a) -> DBT m b) -> DBT m b #

uninterruptibleMask :: ((forall a. DBT m a -> DBT m a) -> DBT m b) -> DBT m b #

generalBracket :: DBT m a -> (a -> ExitCase b -> DBT m c) -> (a -> DBT m b) -> DBT m (b, c) #

(Applicative m, Semigroup a) => Semigroup (DBT m a) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

(<>) :: DBT m a -> DBT m a -> DBT m a #

sconcat :: NonEmpty (DBT m a) -> DBT m a #

stimes :: Integral b => b -> DBT m a -> DBT m a #

(Applicative m, Monoid a) => Monoid (DBT m a) Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

mempty :: DBT m a #

mappend :: DBT m a -> DBT m a -> DBT m a #

mconcat :: [DBT m a] -> DBT m a #

type DB = DBT IO 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 using execute instead of query).
  • 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 query conn "INSERT ... RETURNING ..." ... in cases where you are only inserting a single row, and do not need functionality analogous to 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.

queryOne :: (MonadIO m, ToRow a, FromRow b) => Query -> a -> DBT m (Maybe b) Source #

queryOne_ :: (MonadIO m, FromRow b) => Query -> DBT m (Maybe b) Source #

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

data Abort Source #

Constructors

Abort 

Instances

Instances details
Eq Abort Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

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

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

Show Abort Source # 
Instance details

Defined in Database.PostgreSQL.Transact

Methods

showsPrec :: Int -> Abort -> ShowS #

show :: Abort -> String #

showList :: [Abort] -> ShowS #

Exception Abort Source # 
Instance details

Defined in Database.PostgreSQL.Transact

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. aborts is global. It affects everything before and after it is called. Duplicate aborts 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.