hasql-transaction-0.8: A composable abstraction over the retryable transactions for Hasql

Safe HaskellNone
LanguageHaskell2010

Hasql.Transaction

Contents

Description

Arrow DSL for composition of transactions with automated conflict resolution.

Synopsis

Session

transact :: Transaction i o -> i -> Session o Source #

Execute an alternating transaction arrow providing an input for it.

Transaction

data Transaction i o Source #

Composable transaction providing for automated conflict resolution with input i and output o. Supports alternative branching.

Mode and level is associated with the transaction, which makes them participate in composition. In a composed transaction they become the strictest of the ones associated with the transactions that constitute it. This allows you to safely compose transactions with different ACID guarantees.

Instances
Arrow Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

arr :: (b -> c) -> Transaction b c #

first :: Transaction b c -> Transaction (b, d) (c, d) #

second :: Transaction b c -> Transaction (d, b) (d, c) #

(***) :: Transaction b c -> Transaction b' c' -> Transaction (b, b') (c, c') #

(&&&) :: Transaction b c -> Transaction b c' -> Transaction b (c, c') #

ArrowZero Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

zeroArrow :: Transaction b c #

ArrowPlus Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

(<+>) :: Transaction b c -> Transaction b c -> Transaction b c #

ArrowChoice Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

left :: Transaction b c -> Transaction (Either b d) (Either c d) #

right :: Transaction b c -> Transaction (Either d b) (Either d c) #

(+++) :: Transaction b c -> Transaction b' c' -> Transaction (Either b b') (Either c c') #

(|||) :: Transaction b d -> Transaction c d -> Transaction (Either b c) d #

Profunctor Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

dimap :: (a -> b) -> (c -> d) -> Transaction b c -> Transaction a d #

lmap :: (a -> b) -> Transaction b c -> Transaction a c #

rmap :: (b -> c) -> Transaction a b -> Transaction a c #

(#.) :: Coercible c b => q b c -> Transaction a b -> Transaction a c #

(.#) :: Coercible b a => Transaction b c -> q a b -> Transaction a c #

Choice Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

left' :: Transaction a b -> Transaction (Either a c) (Either b c) #

right' :: Transaction a b -> Transaction (Either c a) (Either c b) #

Strong Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

first' :: Transaction a b -> Transaction (a, c) (b, c) #

second' :: Transaction a b -> Transaction (c, a) (c, b) #

Functor (Transaction i) Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

fmap :: (a -> b) -> Transaction i a -> Transaction i b #

(<$) :: a -> Transaction i b -> Transaction i a #

Applicative (Transaction i) Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

pure :: a -> Transaction i a #

(<*>) :: Transaction i (a -> b) -> Transaction i a -> Transaction i b #

liftA2 :: (a -> b -> c) -> Transaction i a -> Transaction i b -> Transaction i c #

(*>) :: Transaction i a -> Transaction i b -> Transaction i b #

(<*) :: Transaction i a -> Transaction i b -> Transaction i a #

Alternative (Transaction i) Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

empty :: Transaction i a #

(<|>) :: Transaction i a -> Transaction i a -> Transaction i a #

some :: Transaction i a -> Transaction i [a] #

many :: Transaction i a -> Transaction i [a] #

Category Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

id :: Transaction a a #

(.) :: Transaction b c -> Transaction a b -> Transaction a c #

Semigroupoid Transaction Source # 
Instance details

Defined in Hasql.Transaction.Transaction

Methods

o :: Transaction j k1 -> Transaction i j -> Transaction i k1 #

statement :: Mode -> Level -> Statement i o -> Transaction i o Source #

Execute a single statement under a mode and level.

Warning: The statement must not be transaction-related like BEGIN, COMMIT or ABORT, otherwise you'll break the abstraction.

sql :: Mode -> Level -> ByteString -> Transaction () () Source #

Execute a possibly multistatement SQL string under a mode and level. SQL strings cannot be dynamically parameterized or produce a result.

Warning: SQL must not be transaction-related like BEGIN, COMMIT or ABORT, otherwise you'll break the abstraction.

session :: Mode -> Level -> (i -> Session o) -> Transaction i o Source #

Execute a composition of statements under the same mode and level.

Warning:

  1. You must know that it is possible to break the abstraction, if you execute statements such as BEGIN inside of the session.
  2. For the same reason you cannot execute other transactions inside of that session.
  3. You must beware that in case of conflicts any IO code that you may lift into session will get executed multiple times. This is the way the automatic conflict resolution works: the transaction gets retried, when a conflict arises. So be cautious about doing any mutations or rocket launches in that IO! Simply pinging for things such as current time is totally fine though. Still it's not recommended because it's often a symptom of bad application design.

Due to the mentioned it's highly advised to keep all the session code inside of the definition of a transaction. Thus you'll be guaranteed to have control over what's going on inside of the executed session and it will not be possible for this code to be affected by any outside changes or used elsewhere.

condemn :: Transaction () () Source #

Cause transaction to eventually roll back.

This allows to perform some transactional actions, collecting their results, and decide, whether to commit the introduced changes to the DB based on those results, as well as emit those results outside of the transaction.

retry :: Transaction i o Source #

Fail the alternation branch, retrying with the other. Same as empty and zeroArrow.

Beware that if all your alternatives end up being a retry, you'll get yourself a perfect infinite loop.

Settings

data Mode Source #

Execution mode: either read or write.

Constructors

Read

Read-only. No writes possible.

Write

Write and commit.

Instances
Bounded Mode Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Enum Mode Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Eq Mode Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

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

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

Ord Mode Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

compare :: Mode -> Mode -> Ordering #

(<) :: Mode -> Mode -> Bool #

(<=) :: Mode -> Mode -> Bool #

(>) :: Mode -> Mode -> Bool #

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

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

Show Mode Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

data Level Source #

Transaction isolation level.

For reference see the Postgres' documentation.

Instances
Bounded Level Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Enum Level Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Eq Level Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

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

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

Ord Level Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

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

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Show Level Source # 
Instance details

Defined in Hasql.Transaction.Requisites.Model

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Reexports

This module also reexports the following types for you to require lesser imports:

FAQ

Why does transaction have to be an arrow, why is monad or applicative not enough?

Arrow allows us to determine the read mode and isolation level, while composing transactions in such a way that one can depend on the result of the other.

A monadic interface wouldn't allow us to do the first, namely: to compose the modes and levels.

An applicative interface wouldn't allow the second: to make a transaction depend on the result of the other. For details see the docs on the Transaction type.