pg-store-0.5.0: Simple storage interface to PostgreSQL

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

Database.PostgreSQL.Store

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 :: 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 :: PrepQuery a r -> Errand () Source #

Prepare a preparable query.

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.

Query

data Query a Source #

Query object

Constructors

Query 

Fields

Instances

ErrandQuery Query r Source # 

Associated Types

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

Eq (Query a) Source # 

Methods

(==) :: Query a -> Query a -> Bool #

(/=) :: Query a -> Query a -> Bool #

Ord (Query a) Source # 

Methods

compare :: Query a -> Query a -> Ordering #

(<) :: Query a -> Query a -> Bool #

(<=) :: Query a -> Query a -> Bool #

(>) :: Query a -> Query a -> Bool #

(>=) :: Query a -> Query a -> Bool #

max :: Query a -> Query a -> Query a #

min :: Query a -> Query a -> Query a #

Show (Query a) Source # 

Methods

showsPrec :: Int -> Query a -> ShowS #

show :: Query a -> String #

showList :: [Query a] -> ShowS #

type ErrandResult Query r Source # 

data PrepQuery ts a Source #

Preparable query object

Constructors

PrepQuery 

Fields

Instances

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 #

Show (PrepQuery ts a) Source # 

Methods

showsPrec :: Int -> PrepQuery ts a -> ShowS #

show :: PrepQuery ts a -> String #

showList :: [PrepQuery ts a] -> ShowS #

type ErrandResult (PrepQuery ts) r Source # 
type ErrandResult (PrepQuery ts) r = Function ts (Errand r)

pgQuery :: QuasiQuoter Source #

Generate a Query. This utilizes an intermediate query generator of type QueryGenerator ().

See Database.PostgreSQL.Store.Query.TH for detailed description of the language accepted by this quasi quoter.

pgPrepQuery :: QuasiQuoter Source #

Generate a PrepQuery. The intermediate query generator has type QueryGenerator (Tuple ts) where ts has kind [Type]. ts represents the types of the parameters to this prepared query.

It is highly recommended that supply a type signature, if you give the resulting expression a name, to avoid ambiguity.

q :: PrepQuery '[Int, String] User
q = [pgPrepQuery| SELECT #User(u) FROM @User u WHERE age < $(param0) AND name LIKE $(param1) |]

See Database.PostgreSQL.Store.Query.TH for detailed description of the language accepted by this quasi quoter.

pgQueryGen :: QuasiQuoter Source #

Generate a QueryGenerator expression.

See Database.PostgreSQL.Store.Query.TH for detailed description of the language accepted by this quasi quoter.

Types

newtype Oid :: * #

Constructors

Oid CUInt 

Instances

Eq Oid 

Methods

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

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

Ord Oid 

Methods

compare :: Oid -> Oid -> Ordering #

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

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

(>) :: Oid -> Oid -> Bool #

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

max :: Oid -> Oid -> Oid #

min :: Oid -> Oid -> Oid #

Read Oid 
Show Oid 

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

Storable Oid 

Methods

sizeOf :: Oid -> Int #

alignment :: Oid -> Int #

peekElemOff :: Ptr Oid -> Int -> IO Oid #

pokeElemOff :: Ptr Oid -> Int -> Oid -> IO () #

peekByteOff :: Ptr b -> Int -> IO Oid #

pokeByteOff :: Ptr b -> Int -> Oid -> IO () #

peek :: Ptr Oid -> IO Oid #

poke :: Ptr Oid -> Oid -> IO () #

Entity

class KnownNat (Width a) => Entity a where Source #

An entity that is used as a parameter or result of a query.

Associated Types

type Width a :: Nat Source #

Number of values of which the entity consists

Methods

genEntity :: QueryGenerator a Source #

Embed the entity into the query.

genEntity :: (Generic a, GEntity (Rep a)) => QueryGenerator a Source #

Embed the entity into the query.

parseEntity :: RowParser (Width a) a Source #

Retrieve an instance of a from the result set.

parseEntity :: (Generic a, GEntity (Rep a), Width a ~ GEntityWidth (Rep a)) => RowParser (Width a) a Source #

Retrieve an instance of a from the result set.

Instances

Entity Bool Source #
boolean
Entity Double Source #

Any floating-point number

Entity Float Source #

Any floating-point number

Entity Int Source #

Any integer

Entity Int8 Source #

Any integer

Entity Int16 Source #

Any integer

Entity Int32 Source #

Any integer

Entity Int64 Source #

Any integer

Entity Integer Source #

Any integer

Entity Word Source #

Any unsigned integer

Entity Word8 Source #

Any unsigned integer

Entity Word16 Source #

Any unsigned integer

Entity Word32 Source #

Any unsigned integer

Entity Word64 Source #

Any unsigned integer

Entity ByteString Source #

bytea - byte array encoded in hex format

Entity ByteString Source #

bytea - byte array encoded in hex format

Entity Scientific Source #

Any numeric type

Entity String Source #

char, varchar or text - UTF-8 encoded; does not allow NULL characters

Entity Text Source #

char, varchar or text - UTF-8 encoded; does not allow NULL characters

Entity Value Source #

json or jsonb

Entity Text Source #

char, varchar or text - UTF-8 encoded; does not allow NULL characters

Entity Natural Source #

Any unsigned integer

Entity a => Entity (Maybe a) Source #

A value which may be NULL.

Associated Types

type Width (Maybe a) :: Nat Source #

GenericEntity (a, b) => Entity (a, b) Source #

Chain of 2 entities

Associated Types

type Width (a, b) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b) Source #

parseEntity :: RowParser (Width (a, b)) (a, b) Source #

GenericEntity (a, b, c) => Entity (a, b, c) Source #

Chain of 3 entities

Associated Types

type Width (a, b, c) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c) Source #

parseEntity :: RowParser (Width (a, b, c)) (a, b, c) Source #

GenericEntity (a, b, c, d) => Entity (a, b, c, d) Source #

Chain of 4 entities

Associated Types

type Width (a, b, c, d) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d) Source #

parseEntity :: RowParser (Width (a, b, c, d)) (a, b, c, d) Source #

GenericEntity (a, b, c, d, e) => Entity (a, b, c, d, e) Source #

Chain of 5 entities

Associated Types

type Width (a, b, c, d, e) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d, e) Source #

parseEntity :: RowParser (Width (a, b, c, d, e)) (a, b, c, d, e) Source #

GenericEntity (a, b, c, d, e, f) => Entity (a, b, c, d, e, f) Source #

Chain of 6 entities

Associated Types

type Width (a, b, c, d, e, f) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d, e, f) Source #

parseEntity :: RowParser (Width (a, b, c, d, e, f)) (a, b, c, d, e, f) Source #

GenericEntity (a, b, c, d, e, f, g) => Entity (a, b, c, d, e, f, g) Source #

Chain of 7 entities

Associated Types

type Width (a, b, c, d, e, f, g) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d, e, f, g) Source #

parseEntity :: RowParser (Width (a, b, c, d, e, f, g)) (a, b, c, d, e, f, g) Source #

Tables

data Table Source #

Description of a table

Constructors

Table 

Fields

Instances

Eq Table Source # 

Methods

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

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

Ord Table Source # 

Methods

compare :: Table -> Table -> Ordering #

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

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

(>) :: Table -> Table -> Bool #

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

max :: Table -> Table -> Table #

min :: Table -> Table -> Table #

Show Table Source # 

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

class Entity a => TableEntity a where Source #

Table entity with extra information about its name and column names

Methods

describeTableType :: Tagged a Table Source #

Describe the table type.

describeTableType :: GenericTable a => Tagged a Table Source #

Describe the table type.

Errors

data ExecStatus :: * #

Constructors

EmptyQuery

The string sent to the server was empty.

CommandOk

Successful completion of a command returning no data.

TuplesOk

Successful completion of a command returning data (such as a SELECT or SHOW).

CopyOut

Copy Out (from server) data transfer started.

CopyIn

Copy In (to server) data transfer started.

CopyBoth

Copy In/Out data transfer started.

BadResponse

The server's response was not understood.

NonfatalError

A nonfatal error (a notice or warning) occurred.

FatalError

A fatal error occurred.

SingleTuple

The PGresult contains a single result tuple from the current command. This status occurs only when single-row mode has been selected for the query.