pg-store-0.2: 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 #

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 :: Query a -> Errand Result Source #

Execute a query and return the internal raw result.

execute' :: Query a -> Errand Int Source #

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

query :: Entity a => Query a -> Errand [a] Source #

Execute a query and process its result set.

queryWith :: Query a -> RowParser a -> Errand [a] Source #

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

insert :: TableEntity a => a -> Errand Bool Source #

Insert a row into a Table.

insertMany :: TableEntity a => [a] -> Errand Int Source #

Insert many rows into a Table.

deleteAll :: TableEntity a => proxy a -> Errand Int Source #

Delete all rows of a Table.

findAll :: TableEntity a => Errand [a] Source #

Find every row of a Table.

create :: TableEntity a => proxy a -> Errand () Source #

Create the given Table type.

Query

data Query a Source #

Query

Constructors

Query 

Instances

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 #

FromQueryBuilder (Query a) Source # 

pgsq :: QuasiQuoter Source #

Generate queries conveniently. See BuildQuery to find out which types can be produced.

castQuery :: Query a -> Query b Source #

Cast the query's result type.

Entity

class Entity a where Source #

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

Methods

insertEntity :: a -> QueryBuilder Source #

Insert an instance of a into the query.

insertEntity :: (GenericEntity a, GEntity (AnalyzeEntity a)) => a -> QueryBuilder Source #

Insert an instance of a into the query.

parseEntity :: RowParser a Source #

Retrieve an instance of a from the result set.

parseEntity :: (GenericEntity a, GEntity (AnalyzeEntity a)) => RowParser 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

Entity Text Source #

char, varchar or text - UTF-8 encoded

Entity Value Source #

json or jsonb

Entity Text Source #

char, varchar or text - UTF-8 encoded

Entity Natural Source #

Any unsigned integer

Entity TypedValue Source #

Typed column value

Entity Value Source #

Untyped column value

Entity QueryBuilder Source #

QueryBuilder

Entity a => Entity (Maybe a) Source #

A value which may normally not be NULL.

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

2 result entities in sequence

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

3 result entities in sequence

Methods

insertEntity :: (a, b, c) -> QueryBuilder Source #

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

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

4 result entities in sequence

Methods

insertEntity :: (a, b, c, d) -> QueryBuilder Source #

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

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

5 result entities in sequence

Methods

insertEntity :: (a, b, c, d, e) -> QueryBuilder Source #

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

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

6 result entities in sequence

Methods

insertEntity :: (a, b, c, d, e, f) -> QueryBuilder Source #

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

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

7 result entities in sequence

Methods

insertEntity :: (a, b, c, d, e, f, g) -> QueryBuilder Source #

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

Tables

class Entity a => TableEntity a where Source #

Classify a type which can be used as a table.

Methods

describeTableType :: proxy a -> Table Source #

Describe the table type.

describeTableType :: GenericTable a => proxy a -> Table Source #

Describe the table type.

class Entity a => ColumnEntity a where Source #

Classify a type which can be used as a column in a table.

Minimal complete definition

describeColumnType

Methods

describeColumnType :: proxy a -> ColumnType Source #

Describe the column type

Instances

ColumnEntity Bool Source # 
ColumnEntity Double Source # 
ColumnEntity Float Source # 
ColumnEntity Int Source # 
ColumnEntity Int8 Source # 
ColumnEntity Int16 Source # 
ColumnEntity Int32 Source # 
ColumnEntity Int64 Source # 
ColumnEntity Integer Source # 
ColumnEntity Word Source # 
ColumnEntity Word8 Source # 
ColumnEntity Word16 Source # 
ColumnEntity Word32 Source # 
ColumnEntity Word64 Source # 
ColumnEntity ByteString Source # 
ColumnEntity ByteString Source # 
ColumnEntity Scientific Source # 
ColumnEntity String Source # 
ColumnEntity Text Source # 
ColumnEntity Value Source # 
ColumnEntity Text Source # 
ColumnEntity Natural Source # 
ColumnEntity a => ColumnEntity (Maybe a) Source # 

Methods

describeColumnType :: proxy (Maybe a) -> ColumnType Source #

data Table Source #

Description of a table

Constructors

Table 

Fields

data ColumnType Source #

Description of a column type

Constructors

ColumnType 

Fields

data Column Source #

Desciption of a column

Constructors

Column 

Fields

Errors

data ErrandError Source #

Error during errand

Constructors

NoResult

No Result has been returned.

UserError String

A user has thrown an error.

ExecError ExecStatus ErrorCode ByteString ByteString ByteString

Query execution failed.

ParseError RowError

Result processing failed.