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.Query

Contents

Description

 

Synopsis

Query

data Query Source #

Query including statement and parameters

Use the pgsq quasi-quoter to conveniently create queries.

Constructors

Query 

Fields

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.

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.

Helpers

quoteIdentifier :: String -> String Source #

Properly quote an identifier.

Query builder

class QueryCode s Source #

Minimal complete definition

appendCode, appendStringCode

Instances

QueryCode ByteString Source # 

Associated Types

type Code ByteString :: *

QueryCode String Source # 

Associated Types

type Code String :: *

QueryCode [Q Exp] Source # 

Associated Types

type Code [Q Exp] :: *

Methods

appendCode :: [Q Exp] -> Code [Q Exp] -> [Q Exp]

appendStringCode :: [Q Exp] -> String -> [Q Exp]

class QueryBuildable s p o | s p -> o Source #

Can build o using s and [p].

Minimal complete definition

buildQuery

type QueryBuilder s p = State (BuilderState s p) () Source #

Query builder

runQueryBuilder :: (QueryBuildable s p o, Monoid s) => QueryBuilder s p -> o Source #

Run query builder.

writeCode :: QueryCode s => Code s -> QueryBuilder s p Source #

Write code.

writeStringCode :: QueryCode s => String -> QueryBuilder s p Source #

Write string code.

writeIdentifier :: QueryCode s => String -> QueryBuilder s p Source #

Add an identifier.

writeAbsIdentifier :: QueryCode s => String -> String -> QueryBuilder s p Source #

Add an absolute identifier.

writeParam :: QueryCode s => p -> QueryBuilder s p Source #

Embed a parameter.

writeColumn :: (Column p, QueryCode s) => p -> QueryBuilder s Value Source #

Embed a value parameter.

intercalateBuilder :: QueryBuilder s p -> [QueryBuilder s p] -> QueryBuilder s p Source #

Do something between other builders.