postgresql-tx-squeal-0.3.0.0: postgresql-tx interfacing for use with squeal-postgresql.
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Tx.Squeal

Synopsis

Documentation

type SquealEnv r = TxEnv SquealConnection r :: Constraint Source #

Runtime environment needed to run squeal-postgresql via postgresql-tx.

Since: 0.2.0.0

type SquealM a = forall r. SquealEnv r => TxM r a Source #

Monad type alias for running squeal-postgresql via postgresql-tx.

Since: 0.2.0.0

newtype SquealTxM' (db :: SchemasType) r a Source #

A newtype wrapper around TxM which includes the squeal SchemasType parameter db. This is used only as type information. You can easily convert TxM to and from SquealTxM' by using the SquealTxM' constructor and fromSquealTxM function, respectively.

In practice, you will likely prefer to use the SquealTxM type alias as it includes the SquealEnv constraint on r.

Since: 0.2.0.0

Constructors

SquealTxM 

Fields

Instances

Instances details
Monad (SquealTxM' db r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Squeal.Internal

Methods

(>>=) :: SquealTxM' db r a -> (a -> SquealTxM' db r b) -> SquealTxM' db r b #

(>>) :: SquealTxM' db r a -> SquealTxM' db r b -> SquealTxM' db r b #

return :: a -> SquealTxM' db r a #

Functor (SquealTxM' db r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Squeal.Internal

Methods

fmap :: (a -> b) -> SquealTxM' db r a -> SquealTxM' db r b #

(<$) :: a -> SquealTxM' db r b -> SquealTxM' db r a #

Applicative (SquealTxM' db r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Squeal.Internal

Methods

pure :: a -> SquealTxM' db r a #

(<*>) :: SquealTxM' db r (a -> b) -> SquealTxM' db r a -> SquealTxM' db r b #

liftA2 :: (a -> b -> c) -> SquealTxM' db r a -> SquealTxM' db r b -> SquealTxM' db r c #

(*>) :: SquealTxM' db r a -> SquealTxM' db r b -> SquealTxM' db r b #

(<*) :: SquealTxM' db r a -> SquealTxM' db r b -> SquealTxM' db r a #

(TypeError ('Text "MonadIO is banned in SquealTxM'; use 'SquealTxM . unsafeRunIOInTxM' if you are sure this is safe IO") :: Constraint) => MonadIO (SquealTxM' db r) Source #

The SquealTxM' monad discourages performing arbitrary IO within a transaction, so this instance generates a type error when client code tries to call liftIO.

Note that we specialize this instance for SquealTxM' rather than derive it via newtype so we can provide a better error message.

Since: 0.2.0.0

Instance details

Defined in Database.PostgreSQL.Tx.Squeal.Internal

Methods

liftIO :: IO a -> SquealTxM' db r a #

type SquealTxM (db :: SchemasType) a = forall r. SquealEnv r => SquealTxM' db r a Source #

Alias for SquealTxM' but has the SquealEnv constraint applied to r.

Since: 0.2.0.0

data SquealConnection Source #

Used in the SquealEnv to specify the Connection to use. Should produce the same Connection if called multiple times in the same transaction. Usually you will want to use mkSquealConnection to get one.

Since: 0.2.0.0

getRow :: Row -> Result y -> SquealTxM db y Source #

Analogue of getRow.

Since: 0.1.0.0

firstRow :: Result y -> SquealTxM db (Maybe y) Source #

Analogue of firstRow.

Since: 0.1.0.0

getRows :: Result y -> SquealTxM db [y] Source #

Analogue of getRows.

Since: 0.1.0.0

nextRow :: Row -> Result y -> Row -> SquealTxM db (Maybe (Row, y)) Source #

Analogue of nextRow.

Since: 0.1.0.0

ntuples :: Result y -> SquealTxM db Row Source #

Analogue of ntuples.

Since: 0.1.0.0

nfields :: Result y -> SquealTxM db Column Source #

Analogue of nfields.

Since: 0.1.0.0

resultStatus :: Result y -> SquealTxM db ExecStatus Source #

Analogue of resultStatus.

Since: 0.1.0.0

okResult :: Result y -> SquealTxM db () Source #

Analogue of okResult.

Since: 0.2.0.0

resultErrorCode :: Result y -> SquealTxM db (Maybe ByteString) Source #

Analogue of resultErrorCode.

Since: 0.1.0.0

executeParams :: Statement db x y -> x -> SquealTxM db (Result y) Source #

Analogue of executeParams.

Since: 0.1.0.0

executeParams_ :: Statement db x () -> x -> SquealTxM db () Source #

Analogue of executeParams_.

Since: 0.1.0.0

execute :: Statement db () y -> SquealTxM db (Result y) Source #

Analogue of execute.

Since: 0.1.0.0

execute_ :: Statement db () () -> SquealTxM db () Source #

Analogue of execute_.

Since: 0.1.0.0

executePrepared :: Traversable list => Statement db x y -> list x -> SquealTxM db (list (Result y)) Source #

Analogue of executePrepared.

Since: 0.1.0.0

executePrepared_ :: Foldable list => Statement db x () -> list x -> SquealTxM db () Source #

Analogue of executePrepared_.

Since: 0.1.0.0

manipulateParams :: (GenericParams db params x xs, GenericRow row y ys) => Manipulation '[] db params row -> x -> SquealTxM db (Result y) Source #

Analogue of manipulateParams.

Since: 0.1.0.0

manipulateParams_ :: GenericParams db params x xs => Manipulation '[] db params '[] -> x -> SquealTxM db () Source #

Analogue of manipulateParams_.

Since: 0.1.0.0

manipulate :: GenericRow row y ys => Manipulation '[] db '[] row -> SquealTxM db (Result y) Source #

Analogue of manipulate.

Since: 0.1.0.0

manipulate_ :: Manipulation '[] db '[] '[] -> SquealTxM db () Source #

Analogue of manipulate_.

Since: 0.1.0.0

runQueryParams :: (GenericParams db params x xs, IsRecord y ys, AllZip FromField row ys) => Query '[] '[] db params row -> x -> SquealTxM db (Result y) Source #

Analogue of runQueryParams.

Since: 0.1.0.0

runQuery :: (IsRecord y ys, AllZip FromField row ys) => Query '[] '[] db '[] row -> SquealTxM db (Result y) Source #

Analogue of runQuery.

Since: 0.1.0.0

traversePrepared :: (GenericParams db params x xs, Traversable list, IsRecord y ys, AllZip FromField row ys) => Manipulation '[] db params row -> list x -> SquealTxM db (list (Result y)) Source #

Analogue of traversePrepared.

Since: 0.1.0.0

forPrepared :: (GenericParams db params x xs, Traversable list, IsRecord y ys, AllZip FromField row ys) => list x -> Manipulation '[] db params row -> SquealTxM db (list (Result y)) Source #

Analogue of forPrepared.

Since: 0.1.0.0

traversePrepared_ :: (GenericParams db params x xs, Foldable list) => Manipulation '[] db params '[] -> list x -> SquealTxM db () Source #

Analogue of traversePrepared_.

Since: 0.1.0.0

forPrepared_ :: (GenericParams db params x xs, Foldable list) => list x -> Manipulation '[] db params '[] -> SquealTxM db () Source #

Analogue of forPrepared_.

Since: 0.1.0.0

transactionally :: SquealEnv r => TransactionMode -> r -> TxM r a -> IO a Source #

Analogue of transactionally.

Since: 0.1.0.0

transactionally_ :: SquealEnv r => r -> TxM r a -> IO a Source #

Analogue of transactionally_.

Since: 0.1.0.0

transactionallySerializable :: SquealEnv r => r -> TxM r a -> IO a Source #

Specialization of transactionallyRetry which uses Serializable and shouldRetryTx to automatically retry the transaction on serialization_failure or deadlock_detected.

Note that any IO that occurs inside the TxM may be executed multiple times.

Since: 0.2.0.0

transactionallyRetry :: (SquealEnv r, Exception e) => TransactionMode -> (e -> Bool) -> r -> TxM r a -> IO a Source #

Analogue of transactionallyRetry.

Note that any IO that occurs inside the TxM may be executed multiple times.

Since: 0.2.0.0

ephemerally :: SquealEnv r => TransactionMode -> r -> TxM r a -> IO a Source #

Analogue of ephemerally.

Since: 0.1.0.0

ephemerally_ :: SquealEnv r => r -> TxM r a -> IO a Source #

Analogue of ephemerally_.

Since: 0.1.0.0