postgresql-typed-0.3.0: A PostgreSQL access library with compile-time SQL type inference

Copyright2015 Dylan Simon
Safe HaskellNone
LanguageHaskell98

Database.PostgreSQL.Typed.Types

Contents

Description

Classes to support type inference, value encoding/decoding, and instances to support built-in PostgreSQL types.

Synopsis

Basic types

data PGValue Source

A value passed to or from PostgreSQL in raw format.

Constructors

PGNullValue 
PGTextValue PGTextValue

The standard text encoding format (also used for unknown formats)

PGBinaryValue PGBinaryValue

Special binary-encoded data. Not supported in all cases.

Instances

type PGValues = [PGValue] Source

A list of (nullable) data values, e.g. a single row or query parameters.

pgQuote :: String -> String Source

Produce a SQL string literal by wrapping (and escaping) a string with single quotes.

data PGTypeName t Source

A proxy type for PostgreSQL types. The type argument should be an (internal) name of a database type (see \dT+).

Constructors

PGTypeProxy 

data PGTypeEnv Source

Parameters that affect how marshalling happens. Currenly we force all other relevant parameters at connect time.

Constructors

PGTypeEnv 

Fields

pgIntegerDatetimes :: Bool

If integer_datetimes is on; only relevant for binary encoding.

Marshalling classes

class KnownSymbol t => PGParameter t a where Source

A PGParameter t a instance describes how to encode a PostgreSQL type t from a.

Minimal complete definition

pgEncode

Methods

pgEncode :: PGTypeName t -> a -> PGTextValue Source

Encode a value to a PostgreSQL text representation.

pgLiteral :: PGTypeName t -> a -> String Source

Encode a value to a (quoted) literal value for use in SQL statements. Defaults to a quoted version of pgEncode

Instances

PGStringType t => PGParameter t Text 
PGStringType t => PGParameter t Text 
PGStringType t => PGParameter t ByteString 
PGStringType t => PGParameter t ByteString 
PGStringType t => PGParameter t String 
PGLiteralType t a => PGParameter t a 
PGParameter "\"char\"" Char 
PGParameter "boolean" Bool 
PGParameter "bytea" ByteString 
PGParameter "bytea" ByteString 
PGParameter "date" Day 
PGParameter "interval" DiffTime 
PGParameter "numeric" Rational 
PGParameter "time without time zone" TimeOfDay 
PGParameter "timestamp with time zone" UTCTime 
PGParameter "timestamp without time zone" LocalTime 
PGParameter "uuid" UUID 
(PGRangeType tr t, PGParameter t a) => PGParameter tr (Range a) 

class (PGParameter t a, PGBinaryType t) => PGBinaryParameter t a Source

Minimal complete definition

pgEncodeBinary

Instances

(PGStringType t, PGBinaryType t) => PGBinaryParameter t String 
(PGStringType t, PGBinaryType t) => PGBinaryParameter t ByteString 
(PGStringType t, PGBinaryType t) => PGBinaryParameter t ByteString 
(PGStringType t, PGBinaryType t) => PGBinaryParameter t Text 
(PGStringType t, PGBinaryType t) => PGBinaryParameter t Text 
PGBinaryParameter "\"char\"" Char 
PGBinaryParameter "bigint" Int64 
PGBinaryParameter "boolean" Bool 
PGBinaryParameter "bytea" ByteString 
PGBinaryParameter "bytea" ByteString 
PGBinaryParameter "date" Day 
PGBinaryParameter "double precision" Double 
PGBinaryParameter "integer" Int32 
PGBinaryParameter "interval" DiffTime 
PGBinaryParameter "numeric" Rational 
PGBinaryParameter "numeric" Scientific 
PGBinaryParameter "oid" OID 
PGBinaryParameter "real" Float 
PGBinaryParameter "smallint" Int16 
PGBinaryParameter "time without time zone" TimeOfDay 
PGBinaryParameter "timestamp with time zone" UTCTime 
PGBinaryParameter "timestamp without time zone" LocalTime 
PGBinaryParameter "uuid" UUID 

class KnownSymbol t => PGColumn t a where Source

A PGColumn t a instance describes how te decode a PostgreSQL type t to a.

Methods

pgDecode :: PGTypeName t -> PGTextValue -> a Source

Decode the PostgreSQL text representation into a value.

Instances

PGStringType t => PGColumn t Text 
PGStringType t => PGColumn t Text 
PGStringType t => PGColumn t ByteString 
PGStringType t => PGColumn t ByteString 
PGStringType t => PGColumn t String 
PGLiteralType t a => PGColumn t a 
PGColumn "\"char\"" Char 
PGColumn "boolean" Bool 
PGColumn "bytea" ByteString 
PGColumn "bytea" ByteString 
PGColumn "date" Day 
PGColumn "interval" DiffTime

Representation of DiffTime as interval. PostgreSQL stores months and days separately in intervals, but DiffTime does not. We collapse all interval fields into seconds

PGColumn "numeric" Rational

High-precision representation of Rational as numeric. Unfortunately, numeric has an NaN, while Rational does not. NaN numeric values will produce exceptions.

PGColumn "time without time zone" TimeOfDay 
PGColumn "timestamp with time zone" UTCTime 
PGColumn "timestamp without time zone" LocalTime 
PGColumn "uuid" UUID 
(PGRangeType tr t, PGColumn t a) => PGColumn tr (Range a) 

class KnownSymbol t => PGBinaryType t Source

Instances

PGBinaryType "\"char\"" 
PGBinaryType "bigint" 
PGBinaryType "boolean" 
PGBinaryType "bpchar" 
PGBinaryType "bytea" 
PGBinaryType "character varying" 
PGBinaryType "date" 
PGBinaryType "double precision" 
PGBinaryType "integer" 
PGBinaryType "interval" 
PGBinaryType "name" 
PGBinaryType "numeric" 
PGBinaryType "oid" 
PGBinaryType "real" 
PGBinaryType "smallint" 
PGBinaryType "text" 
PGBinaryType "time without time zone" 
PGBinaryType "timestamp with time zone" 
PGBinaryType "timestamp without time zone" 
PGBinaryType "uuid" 

Marshalling utilities

pgEncodeParameter :: PGParameterNull t a => PGTypeEnv -> PGTypeName t -> a -> PGValue Source

Final parameter encoding function used when a (nullable) parameter is passed to a prepared query.

pgEncodeBinaryParameter :: PGBinaryParameterNull t a => PGTypeEnv -> PGTypeName t -> a -> PGValue Source

Final parameter encoding function used when a (nullable) parameter is passed to a prepared query accepting binary-encoded data.

pgEscapeParameter :: PGParameterNull t a => PGTypeEnv -> PGTypeName t -> a -> String Source

Final parameter escaping function used when a (nullable) parameter is passed to be substituted into a simple query.

pgDecodeColumn :: PGColumnNotNull t (Maybe a) => PGTypeEnv -> PGTypeName t -> PGValue -> Maybe a Source

Final column decoding function used for a nullable result value.

pgDecodeColumnNotNull :: PGColumnNotNull t a => PGTypeEnv -> PGTypeName t -> PGValue -> a Source

Final column decoding function used for a non-nullable result value.

pgDecodeBinaryColumn :: PGBinaryColumn t a => PGTypeEnv -> PGTypeName t -> PGValue -> Maybe a Source

Final column decoding function used for a nullable binary-encoded result value.

pgDecodeBinaryColumnNotNull :: (PGColumnNotNull t a, PGBinaryColumn t a) => PGTypeEnv -> PGTypeName t -> PGValue -> a Source

Final column decoding function used for a non-nullable binary-encoded result value.

Specific type support

class (KnownSymbol ta, KnownSymbol t) => PGArrayType ta t | ta -> t, t -> ta Source

Class indicating that the first PostgreSQL type is an array of the second. This implies PGParameter and PGColumn instances that will work for any type using comma as a delimiter (i.e., anything but box). This will only work with 1-dimensional arrays.

Instances

PGArrayType "\"char\"[]" "\"char\"" 
PGArrayType "abstime[]" "abstime" 
PGArrayType "aclitem[]" "aclitem" 
PGArrayType "bigint[]" "bigint" 
PGArrayType "bit[]" "bit" 
PGArrayType "boolean[]" "boolean" 
PGArrayType "box[]" "box" 
PGArrayType "bpchar[]" "bpchar" 
PGArrayType "bytea[]" "bytea" 
PGArrayType "character varying[]" "character varying" 
PGArrayType "cid[]" "cid" 
PGArrayType "cidr[]" "cidr" 
PGArrayType "circle[]" "circle" 
PGArrayType "cstring[]" "cstring" 
PGArrayType "date[]" "date" 
PGArrayType "daterange[]" "daterange" 
PGArrayType "double precision[]" "double precision" 
PGArrayType "gtsvector[]" "gtsvector" 
PGArrayType "inet[]" "inet" 
PGArrayType "int2vector[]" "int2vector" 
PGArrayType "int4range[]" "int4range" 
PGArrayType "int8range[]" "int8range" 
PGArrayType "integer[]" "integer" 
PGArrayType "interval[]" "interval" 
PGArrayType "json[]" "json" 
PGArrayType "line[]" "line" 
PGArrayType "lseg[]" "lseg" 
PGArrayType "macaddr[]" "macaddr" 
PGArrayType "money[]" "money" 
PGArrayType "name[]" "name" 
PGArrayType "numeric[]" "numeric" 
PGArrayType "numrange[]" "numrange" 
PGArrayType "oid[]" "oid" 
PGArrayType "oidvector[]" "oidvector" 
PGArrayType "path[]" "path" 
PGArrayType "point[]" "point" 
PGArrayType "polygon[]" "polygon" 
PGArrayType "real[]" "real" 
PGArrayType "record[]" "record" 
PGArrayType "refcursor[]" "refcursor" 
PGArrayType "regclass[]" "regclass" 
PGArrayType "regconfig[]" "regconfig" 
PGArrayType "regdictionary[]" "regdictionary" 
PGArrayType "regoper[]" "regoper" 
PGArrayType "regoperator[]" "regoperator" 
PGArrayType "regproc[]" "regproc" 
PGArrayType "regprocedure[]" "regprocedure" 
PGArrayType "regtype[]" "regtype" 
PGArrayType "reltime[]" "reltime" 
PGArrayType "smallint[]" "smallint" 
PGArrayType "text[]" "text" 
PGArrayType "tid[]" "tid" 
PGArrayType "time with time zone[]" "time with time zone" 
PGArrayType "time without time zone[]" "time without time zone" 
PGArrayType "timestamp with time zone[]" "timestamp with time zone" 
PGArrayType "timestamp without time zone[]" "timestamp without time zone" 
PGArrayType "tinterval[]" "tinterval" 
PGArrayType "tsquery[]" "tsquery" 
PGArrayType "tsrange[]" "tsrange" 
PGArrayType "tstzrange[]" "tstzrange" 
PGArrayType "tsvector[]" "tsvector" 
PGArrayType "txid_snapshot[]" "txid_snapshot" 
PGArrayType "uuid[]" "uuid" 
PGArrayType "varbit[]" "varbit" 
PGArrayType "xid[]" "xid" 
PGArrayType "xml[]" "xml" 

class (KnownSymbol tr, KnownSymbol t) => PGRangeType tr t | tr -> t Source

Class indicating that the first PostgreSQL type is a range of the second. This implies PGParameter and PGColumn instances that will work for any type.

Instances

PGRangeType "daterange" "date" 
PGRangeType "int4range" "integer" 
PGRangeType "int8range" "bigint" 
PGRangeType "numrange" "numeric" 
PGRangeType "tsrange" "timestamp without time zone" 
PGRangeType "tstzrange" "timestamp with time zone"