postgresql-tx-0.3.0.0: A safe transaction monad for use with various PostgreSQL Haskell libraries.
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Tx.Internal

Synopsis

Disclaimer

Changes to this module will not be reflected in the library's version updates.

Internals

data TxException Source #

Unified exception type thrown from the database.

Each database backend may throw different types of exceptions. As a user of postgresql-tx, ideally we should be able to detect exceptions from the database without needing to catch the database backend's exception type.

The errcode field allows us to introspect the postgresql errcode; see https://www.postgresql.org/docs/current/errcodes-appendix.html

If you need to inspect the exact exception thrown by a database backend, use the cause field.

Constructors

TxException 

type family TxEnvs (xs :: [*]) r :: Constraint where ... Source #

Type family which allows for specifying several TxEnv constraints as a type-level list.

Since: 0.2.0.0

Equations

TxEnvs '[] r = () 
TxEnvs (x ': xs) r = (TxEnv x r, TxEnvs xs r) 

class TxEnv a r where Source #

A type class for specifying how to acquire an environment value to be used for running an implementation of a database library. For example, your database library will likely require some sort of connection value to discharge its effects; in this case, you'd want to define an instance of TxEnv MyDBEnv Connection and use TxM MyDBEnv as your monad for executing transactions.

Note that implementations should take care and ensure that multiple instances are compatible with one another. For example, let's say you have instances for both TxEnv E PgSimple.Connection and TxEnv E LibPQ.Connection; if both of these implementations are grabbing connections from a pool, you will end up with each of those database libraries using different connections, and thus, would be running in separate transactions!

Since: 0.2.0.0

Methods

lookupTxEnv :: r -> a Source #

Acquire a value a via the reader environment r which assists in running a TxM in a transaction.

Since: 0.2.0.0

Instances

Instances details
Select a xs => TxEnv a (HEnv xs) Source #

TxEnv instance for HEnv; selects the first a in the HEnv and makes it available via the runtime environment.

Since: 0.2.0.0

Instance details

Defined in Database.PostgreSQL.Tx.HEnv

Methods

lookupTxEnv :: HEnv xs -> a Source #

newtype TxM r a Source #

The transaction monad. Unifies all database integrations, regardless of library, into a single monad. The r type parameter represents the reader environment needed for applicable database libraries. For example, postgresql-simple needs a Connection to run its functions, so its interface will require that we can obtain a Connection from the r using the TxEnv type class.

Since: 0.2.0.0

Constructors

UnsafeTxM 

Fields

Instances

Instances details
Monad (TxM r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

(>>=) :: TxM r a -> (a -> TxM r b) -> TxM r b #

(>>) :: TxM r a -> TxM r b -> TxM r b #

return :: a -> TxM r a #

Functor (TxM r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

fmap :: (a -> b) -> TxM r a -> TxM r b #

(<$) :: a -> TxM r b -> TxM r a #

MonadFail (TxM r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

fail :: String -> TxM r a #

Applicative (TxM r) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

pure :: a -> TxM r a #

(<*>) :: TxM r (a -> b) -> TxM r a -> TxM r b #

liftA2 :: (a -> b -> c) -> TxM r a -> TxM r b -> TxM r c #

(*>) :: TxM r a -> TxM r b -> TxM r b #

(<*) :: TxM r a -> TxM r b -> TxM r a #

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

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

Since: 0.1.0.0

Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

liftIO :: IO a -> TxM r a #

Semigroup a => Semigroup (TxM r a) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

(<>) :: TxM r a -> TxM r a -> TxM r a #

sconcat :: NonEmpty (TxM r a) -> TxM r a #

stimes :: Integral b => b -> TxM r a -> TxM r a #

Monoid a => Monoid (TxM r a) Source # 
Instance details

Defined in Database.PostgreSQL.Tx.Internal

Methods

mempty :: TxM r a #

mappend :: TxM r a -> TxM r a -> TxM r a #

mconcat :: [TxM r a] -> TxM r a #

unsafeRunIOInTxM :: IO a -> TxM r a Source #

Run an IO action in TxM. Use this function with care - arbitrary IO should only be run within a transaction when truly necessary.

Since: 0.2.0.0

unsafeMkTxM :: (r -> IO a) -> TxM r a Source #

Construct a TxM using a reader function. Use this function with care - arbitrary IO should only be run within a transaction when truly necessary.

Since: 0.2.0.0

unsafeMksTxM :: TxEnv a r => (a -> IO b) -> TxM r b Source #

Similar to unsafeMkTxM but allows for constructing a TxM with a reader function using a specific value from the environment. Use this function with care - arbitrary IO should only be run within a transaction when truly necessary.

Since: 0.2.0.0

unsafeRunTxM :: r -> TxM r a -> IO a Source #

Run a TxM to IO given the database runtime environment r. Use of this function outside of test suites should be rare.

Since: 0.2.0.0

unsafeWithRunInIOTxM :: ((forall a. TxM r a -> IO a) -> IO b) -> TxM r b Source #

Run a TxM action in IO via the provided runner function. Use this function with care - arbitrary IO should only be run within a transaction when truly necessary.

Since: 0.2.0.0

askTxEnv :: TxEnv a r => TxM r a Source #

unsafeLookupTxEnvIO :: TxEnv a r => r -> IO a Source #

Analogous to lookupTxEnv but can be run in IO instead of TxM.

Since: 0.2.0.0

throwExceptionTx :: Exception e => e -> TxM r a Source #

Throw an exception.

Since: 0.2.0.0

mapExceptionTx :: (Exception e, Exception e') => (e -> Maybe e') -> TxM r a -> TxM r a Source #

Catch an exception and map it to another exception type before rethrowing.

Since: 0.2.0.0

errcode'serialization_failure :: String Source #

PostgreSQL errcode for serialization_failure.

errcode'deadlock_detected :: String Source #

PostgreSQL errcode for deadlock_detected.

hasErrcode :: (String -> Bool) -> TxException -> Bool Source #

Checks if the errcode of a TxException matches the supplied predicate. If the errcode is Nothing, returns False.

shouldRetryTx :: TxException -> Bool Source #

Useful as a predicate to indicate when to retry transactions which are run at isolation level serializable

unsafeMkTxException :: Exception e => (e -> Maybe String) -> e -> TxException Source #

Construct a TxException from an errcode accessing function and the cause exception.

Note that this function should only be used by libraries which are implementing a database backend for postgresql-tx.