pg-store-0.0.1: Dead 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

Tables

data TableConstraint Source

Options to mkTable.

Constructors

Unique [Name]

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

ForeignKey [Name] Name [Name]

A combination of fields references another combination of fields from a different table. ForeignKey ['name1, 'name2, ...] ''RefTable ['refname1, 'refname2, ...] works like this table constraint in SQL: FOREIGN KEY (name1, name2, ...) REFERENCES RefTable(refname1, refname2, ...)

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

Implement Table for a data 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 #-}
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 []

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

mkTable ''MovieCast []

data Row a Source

Resolved row

Constructors

Row 

Fields

rowID :: !Int64

Identifier

rowValue :: !a

Value

Instances

HasID Row Source 
Eq a => Eq (Row a) Source 
Ord a => Ord (Row a) Source 
Show a => Show (Row a) Source 
Table a => Result (Row a) Source 

newtype Reference a Source

Reference to a row

Constructors

Reference Int64 

Queries

data Query Source

Query including statement and parameters. Use the pgsq quasi-quoter to conveniently create queries.

Constructors

Query 

Fields

queryStatement :: !ByteString

Statement

queryParams :: ![Value]

Parameters

pgsq :: QuasiQuoter Source

Generate a Query from a SQL statement.

Table and column names

All plain identifiers will be treated as Haskell names. They are going to be resolved to their fully-qualified and quoted version. Beware, the use of names which don't refer to a table type or field will likely result in unknown table or column errors. The associated table name of a type is retrieved using describeTableName. If you don't want a name to be resolved use a quoted identifier.

Example:

{-# LANGUAGE QuasiQuotes #-}
module MyModule where

...

data Table = Table { myField :: Int }
mkTable ''Table []

myQuery :: Query
myQuery = [pgsq| SELECT * FROM Table WHERE myField > 1337 |]

The SQL statement associated with myQuery will be:

SELECT * FROM "MyModule.Table" WHERE "MyModule.myField" > 1337

Variables

You can use reference variables with $myVariable. The variable's type has to be an instance of Column, otherwise it cannot be attached as query parameter.

Example:

magicNumber :: Int
magicNumber = 1337

myQuery :: Query
myQuery = [pgsq| SELECT * FROM Table WHERE myField > $magicNumber |]

Row identifiers

Each instance of (Table a) => Row a, (Table a) => Reference a and each row of the actual table inside the database has an identifier value. These identifiers are used to reference specific rows. The identifier column is exposed via the &MyTable pattern. Identifier field names are resolved using describeTableIdentifier.

Example:

[pgsq| SELECT *
       FROM TableA, TableB
       WHERE refToB = &TableB |]

Note refToB is a field of TableA. In different circumstances one would write such query as follows.

SELECT *
FROM TableA a, Table b
WHERE a.refToB = b.id

mkCreateQuery :: Name -> Q Exp Source

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

Example:

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

Errands

data ResultError Source

Error that occured during result processing

type Errand = ReaderT Connection (ExceptT ErrandError IO) Source

An interaction with the database

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

Run an errand.

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

Execute a query and process its result set. It is essential that all fields required by the underlying result parser are present.

query_ :: Query -> Errand () Source

Execute a query.

insert :: Table a => a -> Errand (Reference a) Source

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

find :: (Table a, HasID i) => i a -> Errand (Row a) Source

Find the row identified by the given reference.

update :: (Table a, HasID i) => i a -> a -> Errand () Source

Update an existing row.

delete :: (Table a, HasID i) => i a -> Errand () Source

Delete a row from the table.