postgresql-typed-0.6.0.1: PostgreSQL interface with compile-time SQL type checking, optional HDBC backend

Safe HaskellNone
LanguageHaskell98

Database.PostgreSQL.Typed

Contents

Synopsis

Introduction

PostgreSQL-Typed is designed with 2 goals in mind: safety and performance. The primary focus is on safety.

To help ensure safety, it uses the PostgreSQL server to parse every query and statement in your code to infer types at compile-time. This means that in theory you cannot get a syntax error at runtime. Getting proper types at compile time has the nice side-effect that it eliminates run-time type casting and usually results in less code. This approach was inspired by MetaHDBC (http://haskell.org/haskellwiki/MetaHDBC) and PG'OCaml (http://pgocaml.berlios.de/).

While compile-time query analysis eliminates many errors, it doesn't eliminate all of them. If you modify the database without recompilation or have an error in a trigger or function, for example, you can still trigger a PGError or other failure (if types change). Also, nullable result fields resulting from outer joins are not detected and need to be handled explicitly.

Based originally on Chris Forno's TemplatePG library. A compatibility interface for that library is provided by Database.PostgreSQL.Typed.TemplatePG which can basically function as a drop-in replacement (and also provides an alternative interface with some additional features).

newtype PGError Source #

PGException is thrown upon encountering an ErrorResponse with severity of ERROR, FATAL, or PANIC. It holds the message of the error.

Constructors

PGError 

Fields

Usage

Basic usage consists of calling pgConnect, pgSQL (Template Haskell quasi-quotation), pgQuery, and pgDisconnect: You must enable TemplateHaskell and/or QuasiQuotes language extensions.

c <- pgConnect
let name = "Joe"
people :: [Int32] <- pgQuery c [pgSQL|SELECT id FROM people WHERE name = ${name}|]
pgDisconnect c

Connections

All database access requires a PGConnection that is created at runtime using pgConnect, and should be explicitly be closed with pgDisconnect when finished.

However, at compile time, PostgreSQL-Typed needs to make its own connection to the database in order to describe queries. By default, it will use the following environment variables:

TPG_DB
the database name to use (default: same as user)
TPG_USER
the username to connect as (default: $USER or postgres)
TPG_PASS
the password to use (default: empty)
TPG_HOST
the host to connect to (default: localhost)
TPG_PORT or TPG_SOCK
the port number or local socket path to connect on (default: 5432)

If you'd like to specify what connection to use directly, use useTPGDatabase at the top level:

useTPGDatabase PGDatabase{ ... }

Note that due to TH limitations, the database must be in-line or in a different module. This call must be processed by the compiler before (above) any other TH calls.

You can set TPG_DEBUG at compile or runtime to get a protocol-level trace.

data PGDatabase Source #

Information for how to connect to a database, to be passed to pgConnect.

Constructors

PGDatabase 

Fields

defaultPGDatabase :: PGDatabase Source #

A database connection with sane defaults: localhost:5432:postgres

data PGConnection Source #

An established connection to the PostgreSQL server. These objects are not thread-safe and must only be used for a single request at a time.

pgConnect :: PGDatabase -> IO PGConnection Source #

Connect to a PostgreSQL server.

pgDisconnect Source #

Arguments

:: PGConnection

a handle from pgConnect

-> IO () 

Disconnect cleanly from the PostgreSQL server.

useTPGDatabase :: PGDatabase -> DecsQ Source #

Specify an alternative database to use during compilation. This lets you override the default connection parameters that are based on TPG environment variables. This should be called as a top-level declaration and produces no code. It uses pgReconnect so is safe to call multiple times with the same database.

Queries

There are two steps to running a query: a Template Haskell quasiquoter to perform type-inference at compile time and create a PGQuery; and a run-time function to execute the query (pgRunQuery, pgQuery, pgExecute).

Compile time

Both TH functions take a single SQL string, which may contain in-line placeholders of the form ${expr} (where expr is any valid Haskell expression) and/or PostgreSQL placeholders of the form $1, $2, etc.

let q = [pgSQL|SELECT id, name, address FROM people WHERE name LIKE ${query++"%"} OR email LIKE $1|] :: PGSimpleQuery [(Int32, String, Maybe String)]

Expression placeholders are substituted with PostgreSQL ones in left-to-right order starting with 1, so must be in places that PostgreSQL allows them (e.g., not identifiers, table names, column names, operators, etc.) However, this does mean that you can repeat expressions using the corresponding PostgreSQL placeholder as above. If there are extra PostgreSQL parameters the may be passed as arguments:

[pgSQL|SELECT id FROM people WHERE name = $1|] :: String -> PGSimpleQuery [Int32]

To produce PGPreparedQuery objects instead of PGSimpleQuery, put a single $ at the beginning of the query. You can also create queries at run-time using rawPGSimpleQuery or rawPGPreparedQuery.

pgSQL :: QuasiQuoter Source #

A quasi-quoter for PGSQL queries.

Used in expression context, it may contain any SQL statement [pgSQL|SELECT ...|]. The statement may contain PostgreSQL-style placeholders ($1, $2, ...) or in-line placeholders (${1+1}) containing any valid Haskell expression (except {}). It will be replaced by a PGQuery object that can be used to perform the SQL statement. If there are more $N placeholders than expressions, it will instead be a function accepting the additional parameters and returning a PGQuery.

Ideally, this mimics postgres' SQL parsing, so that placeholders and expressions will only be expanded when they are in valid positions (i.e., not inside quoted strings). Since ${ is not valid SQL otherwise, there should be no need to escape it.

The statement may start with one of more special flags affecting the interpretation:

?
To disable nullability inference, treating all result values as nullable, thus returning Maybe values regardless of inferred nullability. This makes unexpected NULL errors impossible.
!
To disable nullability inference, treating all result values as not nullable, thus only returning Maybe where requested. This is makes unexpected NULL errors more likely.
$
To create a PGPreparedQuery (using placeholder parameters) rather than the default PGSimpleQuery (using literal substitution).
$(type,...)
To specify specific types for a prepared query (see http://www.postgresql.org/docs/current/static/sql-prepare.html for details), rather than inferring parameter types by default.
#
Only do literal ${} substitution using pgSubstituteLiterals and return a string, not a query.

pgSQL can also be used at the top-level to execute SQL statements at compile-time (without any parameters and ignoring results). Here the query can only be prefixed with ! to make errors non-fatal.

If you want to construct queries out of string variables rather than quasi-quoted strings, you can use the lower-level makePGQuery instead.

Runtime

There are multiple ways to run a PGQuery once it's created (pgQuery, pgExecute), and you can also write your own, but they all reduce to pgRunQuery. These all take a PGConnection and a PGQuery, and return results. How they work depends on the type of query.

PGSimpleQuery simply substitutes the placeholder values literally into into the SQL statement. This should be safe for all currently-supported types.

PGPreparedQuery is a bit more complex: the first time any given prepared query is run on a given connection, the query is prepared. Every subsequent time, the previously-prepared query is re-used and the new placeholder values are bound to it. Queries are identified by the text of the SQL statement with PostgreSQL placeholders in-place, so the exact parameter values do not matter (but the exact SQL statement, whitespace, etc. does). (Prepared queries are released automatically at pgDisconnect, but may be closed early using pgCloseQuery.)

pgQuery :: PGQuery q a => PGConnection -> q -> IO [a] Source #

Run a query and return a list of row results.

pgExecute :: PGQuery q () => PGConnection -> q -> IO Int Source #

Execute a query that does not return results. Return the number of rows affected (or -1 if not known).

pgTransaction :: PGConnection -> IO a -> IO a Source #

Wrap a computation in a pgBegin, pgCommit block, or pgRollback on exception.

TemplatePG compatibility

There is also an older, simpler interface based on TemplatePG that combines both the compile and runtime steps. queryTuples does all the work (queryTuple and execute are convenience functions).

It's a Template Haskell function, so you need to splice it into your program with $(). It requires a PGConnection to a PostgreSQL server, but can't be given one at compile-time, so you need to pass it after the splice:

h <- pgConnect ...
tuples <- $(queryTuples "SELECT * FROM pg_database") h

To pass parameters to a query, include them in the string with {}. Most Haskell expressions should work. For example:

let owner = 33 :: Int32
tuples <- $(queryTuples "SELECT * FROM pg_database WHERE datdba = {owner} LIMIT {2 * 3 :: Int64}") h

TemplatePG provides withTransaction, rollback, and insertIgnore, but they've not been thoroughly tested, so use them at your own risk.

Advanced usage

Types

Most builtin types are already supported. For the most part, exactly equivalent types are all supported (e.g., Int32 for int4) as well as other safe equivalents, but you cannot, for example, pass an Integer as a smallint. To achieve this flexibility, the exact types of all parameters and results must be fully known (e.g., numeric literals will not work).

However you can add support for your own types or add flexibility to existing types by creating new instances of PGParameter (for encoding) and PGColumn (for decoding).

instance PGType "mytype"
instance PGParameter "mytype" MyType where
  pgEncode _ (v :: MyType) = ... :: ByteString
instance PGColumn "mytype" MyType where
  pgDecode _ (s :: ByteString) = ... :: MyType

You can make as many PGParameter and PGColumn instances as you want if you want to support different representations of your type. If you want to use any of the functions in Database.PostgreSQL.Typed.Dynamic, however, such as pgSafeLiteral, you must define a default representation:

instance PGRep MyType where type PGRepType MyType = "mytype"

If you want to support arrays of your new type, you should also provide a PGArrayType instance (or PGRangeType for new ranges). Currently only 1-dimensional arrays are supported.

instance PGType "mytype[]"
instance PGArrayType "mytype[]" "mytype"

Required language extensions: FlexibleInstances, MultiParamTypeClasses, DataKinds

A Note About NULL

Sometimes PostgreSQL cannot automatically determine whether or not a result field can potentially be NULL. In those cases it will assume that it can. Basically, any time a result field is not immediately traceable to an originating table and column (such as when a function is applied to a result column), it's assumed to be nullable and will be returned as a Maybe value. Other values may be decoded without the Maybe wrapper.

You can use NULL values in parameters as well by using Maybe.

Caveats

The types of all parameters and results must be fully known. This may require explicit casts in some cases (especially with numeric literals).

You cannot construct queries at run-time, since they wouldn't be available to be analyzed at compile time (but you can construct them at compile time by writing your own TH functions).

Because of how PostgreSQL handles placeholders, they cannot be used in place of lists (such as IN (?)). You must replace such cases with equivalent arrays (= ANY (?)).

For the most part, any code must be compiled and run against databases that are at least structurally identical. Furthermore, prepared queries also store OIDs for user types, so the generated PGPreparedQuery can only be run on the exact same database or one restored from a dump with OIDs (pg_dump -o). If this is a concern, only use built-in types in prepared queries. (This requirement could be weakened with some work, if there were need.)

Tips

If you find yourself pattern matching on result tuples just to pass them on to functions, you can use uncurryN from the tuple package. The following examples are equivalent.

(a, b, c) <- $(queryTuple "SELECT a, b, c FROM table LIMIT 1")
someFunction a b c
uncurryN someFunction `liftM` $(queryTuple "SELECT a, b, c FROM table LIMIT 1")