pg-store-0.5.0: Simple storage interface to PostgreSQL

Copyright(c) Ole Krüger 2015-2016
LicenseBSD3
MaintainerOle Krüger <ole@vprsm.de>
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Store.Errand

Contents

Description

 

Synopsis

Errand

data Errand a Source #

An interaction with the database

Instances

Monad Errand Source # 

Methods

(>>=) :: Errand a -> (a -> Errand b) -> Errand b #

(>>) :: Errand a -> Errand b -> Errand b #

return :: a -> Errand a #

fail :: String -> Errand a #

Functor Errand Source # 

Methods

fmap :: (a -> b) -> Errand a -> Errand b #

(<$) :: a -> Errand b -> Errand a #

Applicative Errand Source # 

Methods

pure :: a -> Errand a #

(<*>) :: Errand (a -> b) -> Errand a -> Errand b #

(*>) :: Errand a -> Errand b -> Errand b #

(<*) :: Errand a -> Errand b -> Errand a #

Alternative Errand Source # 

Methods

empty :: Errand a #

(<|>) :: Errand a -> Errand a -> Errand a #

some :: Errand a -> Errand [a] #

many :: Errand a -> Errand [a] #

MonadIO Errand Source # 

Methods

liftIO :: IO a -> Errand a #

MonadError ErrandError Errand Source # 

runErrand :: Connection -> Errand a -> IO (Either ErrandError a) Source #

Run an errand.

Execute queries

execute :: ErrandQuery q Result => q r -> ErrandResult q Result Source #

Execute the query and return its internal result.

execute' :: ErrandQuery q Int => q r -> ErrandResult q Int Source #

Same as execute but instead of a Result it returns the number of affected rows.

query :: (Entity r, ErrandQuery q [r]) => q r -> ErrandResult q [r] Source #

Execute a query and process its result set.

queryWith :: (ErrandQuery q [r], KnownNat n) => RowParser n r -> q r -> ErrandResult q [r] Source #

Execute a query and process its result set using the provided RowParser.

Prepare statements

prepare :: PrepQuery a r -> Errand () Source #

Prepare a preparable query.

Transactions

beginTransaction :: Errand () Source #

Begin a transaction.

commitTransaction :: Errand () Source #

Commit transaction.

saveTransaction :: ByteString -> Errand () Source #

Create savepoint within transaction.

rollbackTransaction :: Errand () Source #

Roll back transaction.

rollbackTransactionTo :: ByteString -> Errand () Source #

Roll back to a specific savepoint.

withTransaction :: Errand a -> Errand () Source #

Do something within a transaction.

Helpers

class ErrandQuery q r where Source #

Identifies q as a query object.

Minimal complete definition

executeWith

Associated Types

type ErrandResult q r Source #

A type equal to Errand r or a function which will eventually yield a Errand r

Methods

executeWith :: (Result -> Errand r) -> q x -> ErrandResult q r Source #

Execute the query described in q x and pass its Result to the given function.

Instances

ErrandQuery Query r Source # 

Associated Types

type ErrandResult (Query :: * -> *) r :: * Source #

ErrandQuery Statement r Source # 

Associated Types

type ErrandResult (Statement :: * -> *) r :: * Source #

WithTuple ts => ErrandQuery (PrepQuery ts) r Source # 

Associated Types

type ErrandResult (PrepQuery ts :: * -> *) r :: * Source #

Methods

executeWith :: (Result -> Errand r) -> PrepQuery ts x -> ErrandResult (PrepQuery ts) r Source #