pg-store-0.1.1: 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

Contents

Description

 

Synopsis

Errands

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 # 

data ErrandError Source #

Error during errand

Constructors

NoResult

No Result has been returned.

EmptyResult

Result set is empty.

UserError String

A user has thrown an error.

ExecError ExecStatus ErrorCode ByteString ByteString ByteString

Query execution failed.

ResultError ResultError

Result processing failed.

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.

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.

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

Run an errand.

execute :: Query -> Errand Result Source #

Execute a query and return the internal raw result.

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

Execute a query and process its result set.

query_ :: Query -> Errand () Source #

Execute a query and dismiss its result.

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

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

Queries

data Query Source #

Query including statement and parameters

Use the pgsq quasi-quoter to conveniently create queries.

Constructors

Query 

Fields

pgsq :: QuasiQuoter Source #

This quasi-quoter allows you to generate instances of Query. It lets you write SQL with some small enhancements. pgsq heavily relies on QueryTable which can be implemented by mkTable for a type of your choice.

Some syntax definitions that might be useful later on:

TypeName          ::= UpperAlpha {AlphaNumeric | '_'}
Name              ::= (Alpha | '_') {AlphaNumeric | '_'}
QualifiedTypeName ::= {TypeName '.'} TypeName

Alpha includes all alphabetical characters; UpperAlpha includes all upper-case alphabetical characters; AlphaNumeric includes all alpha-numeric characters.

Embed values

You can embed values whose types implement Column.

ValueExp ::= '$' Name
magicNumber :: Int
magicNumber = 1337

myQuery :: Query
myQuery =
    [pgsq| SELECT * FROM table t WHERE t.column1 > $magicNumber AND t.column2 < $otherNumber |]
    where otherNumber = magicNumber * 2

$magicNumber and $otherNumber are references to values magicNumber and otherNumber.

The quasi-quoter will generate a Query expression similar to the following.

Query "SELECT * FROM table t WHERE t.column1 > $1 AND t.column2 < $2"
      [pack magicNumber, pack otherNumber]

Table names

Types that implement QueryTable associate a table name with themselves. Since the table name is not always known to the user, one can insert it dynamically.

TableNameExp ::= '@' QualifiedTypeName

The @-operators is also an alias for the function ABS. If you have an expression that triggers the quasi-quoter such as @A, but you would like to use the ABS functionality, then simply reformat your expression to @(A) or ABS(A).

instance QueryTable YourType where
    tableName _ = "YourTable"

myQuery :: Query
myQuery =
    [pgsq| SELECT * FROM @YourType WHERE @YourType.column = 1337 |]

The table name will be inlined which results in the following.

Query "SELECT * FROM \"YourTable\" WHERE \"YourTable\".column = 1337" []

Identifier column names

Each instance of QueryTable also provides the name of the identifier column. Using this column name you can identify specific rows of a certain table.

TableIdentExp ::= '&' TypeName

& is also the operator for bitwise-AND. To resolve the ambiguity for expressions like A&B, simply reformat it to A & B or A&(B).

instance QueryTable YourType where
    tableName _   = "YourTable"
    tableIDName _ = "id"

listIDs :: Query
listIDs =
    [pgsq| SELECT &YourType FROM @YourType |]

listIDs is now a query which lists the IDs of each row. This is especially useful in combination with Reference.

fetchIDs :: Errand [Reference YourType]
fetchIDs =
    query [pgsq| SELECT &YourType FROM @YourType |]

Selectors

mkTable will automatically implement Result and QueryTable for you. This allows you to make use of the selector expander.

SelectorExp ::= '#' QualifiedTypeName

# is also the operator for bitwise-XOR. To resolve the ambiguity for expressions like A#B, simply reformat it to A # B or A#(B) or A#"B".

data Actor = Actor {
    actorName :: String,
    actorAge  :: Word
} deriving (Show, Eq, Ord)

mkTable ''Actor []

fetchOldActors :: Errand [Actor]
fetchOldActors =
    query [pgsq| SELECT #Actor FROM @Actor a WHERE a.actorAge >= $oldAge |]
    where oldAge = 70

#Actor will expand to a list of columns that are necessary to construct an instance of Actor. In this case it is equivalent to

@Actor.actorName, @Actor.actorAge

pgss :: QuasiQuoter Source #

Just like pgsq but only produces the statement associated with the query. Referenced values are not inlined, they are simply dismissed.

class QueryTable a where Source #

A type which implements this class can be used as a table in a quasi-quoted query. mkTable can implement this for you.

Minimal complete definition

tableName, tableIDName, tableSelectors

Methods

tableName :: Proxy a -> String Source #

Unquoted name of the table

tableIDName :: Proxy a -> String Source #

Unquoted name of the ID field

tableSelectors :: Proxy a -> [SelectorElement] Source #

Selectors needed to retrieve all fields necessary to construct the type - think SELECT.

Values

data Value Source #

Query parameter or value of a column - see pack on how to generate Values manually but conveniently.

Constructors

Value 

Fields

NullValue 

class Column a where Source #

Types which implement this type class may be used as column types.

Minimal complete definition

pack, unpack, columnTypeName

Methods

pack :: a -> Value Source #

Pack column value.

unpack :: Value -> Maybe a Source #

Unpack column value.

columnTypeName :: Proxy a -> String Source #

Name of the underlying SQL type.

columnAllowNull :: Proxy a -> Bool Source #

May the column be NULL?

columnCheck :: Proxy a -> String -> Maybe String Source #

A condition that must hold true for the column.

columnDescription :: Proxy a -> String -> String Source #

Generate column description in SQL. Think CREATE TABLE.

Instances

Column Bool Source # 
Column Int Source # 
Column Int8 Source # 
Column Int16 Source # 
Column Int32 Source # 
Column Int64 Source # 
Column Integer Source # 
Column Word Source # 
Column Word8 Source # 
Column Word16 Source # 
Column Word32 Source # 
Column Word64 Source # 
Column ByteString Source # 
Column ByteString Source # 
Column Text Source # 
Column Text Source # 
Column UTCTime Source # 
Column Value Source # 
Column [Char] Source # 
Column a => Column (Maybe a) Source # 
QueryTable a => Column (Reference a) Source # 

Results

class Result a where Source #

Allows you to implement a custom result parser for your type. mkTable can implement this for your type.

Minimal complete definition

queryResultProcessor

Instances

Column a => Result (Single a) Source # 
Result (Reference a) Source # 
(Result a, Result b) => Result (a, b) Source #

Combine result parsers sequencially.

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

Methods

queryResultProcessor :: ResultProcessor (a, b, c, d, e) Source #

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

Methods

queryResultProcessor :: ResultProcessor (a, b, c, d, e, f) Source #

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

Methods

queryResultProcessor :: ResultProcessor (a, b, c, d, e, f, g) Source #

data ResultError Source #

Error that occured during result processing

Constructors

TooFewColumnsError Column

Occurs when you're trying to access a column that does not exist.

UnpackError Row Column Oid Format

The value at a given row and column could not be unpacked.

skipColumn :: ResultProcessor () Source #

Move cursor to the next column.

unpackColumn :: Column a => ResultProcessor a Source #

Unpack the current column and move the cursor to the next column.

newtype Single a Source #

Helper type to capture an single column.

Constructors

Single 

Fields

Instances

Eq a => Eq (Single a) Source # 

Methods

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

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

Ord a => Ord (Single a) Source # 

Methods

compare :: Single a -> Single a -> Ordering #

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

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

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

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

max :: Single a -> Single a -> Single a #

min :: Single a -> Single a -> Single a #

Show a => Show (Single a) Source # 

Methods

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

show :: Single a -> String #

showList :: [Single a] -> ShowS #

Column a => Result (Single a) Source # 

Tables

class Table a where Source #

Qualify a as a table type. mkTable can implement this class for you.

Minimal complete definition

insert, find, update, delete, createTableQuery

Methods

insert :: a -> Errand (Reference a) Source #

Insert a row into the table and return a Reference to the inserted row.

insertMany :: [a] -> Errand [Reference a] Source #

Insert multiple rows into the table at once.

find :: Reference a -> Errand a Source #

Find the row identified by the given reference.

update :: Reference a -> a -> Errand () Source #

Update an existing row.

delete :: Reference a -> Errand () Source #

Delete a row from the table.

createTableQuery :: Proxy a -> Query Source #

Generate the query which creates this table inside the database. Use mkCreateQuery for convenience.

mkCreateQuery :: Name -> Q Exp Source #

Generate a Query expression which will create the table described by the given type.

Example:

data Table = Table { myField :: Int }
mkTable ''Table []
...
query_ $(mkCreateQuery ''Table)

mkTable :: Name -> [TableConstraint] -> Q [Dec] Source #

Implement the type classes QueryTable, Table and Result for the given type.

The given type must fulfill these requirements:

  • Data type
  • No type context
  • No type variables
  • One record constructor with 1 or more fields
  • All field types must have an instance of Column

Example:

{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module Movies where

...

data Movie = Movie {
    movieTitle :: String,
    movieYear  :: Int
} deriving Show

mkTable ''Movie []

data Actor = Actor {
    actorName :: String,
    actorAge  :: Int
} deriving Show

mkTable ''Actor [Unique ['actorName], Check [pgss| actorAge >= 18 |]]

data MovieCast = MovieCast {
    movieCastMovie :: Reference Movie,
    movieCastActor :: Reference Actor
} deriving Show

mkTable ''MovieCast [Unique ['movieCastMovie, 'movieCastActor]]

In this example, Reference takes care of adding the FOREIGN KEY constraint, so we don't have to.

data TableConstraint Source #

Options to mkTable.

Constructors

Unique [Name]

A combination of fields must be unique. Unique ['name1, 'name2, ...] works analogous to the table constraint UNIQUE (name1, name2, ...) in SQL.

Check String

The given statement must evaluate to true. Just like CHECK (statement) in SQL.