postgresql-typed-0.4.2.1: 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

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

Fields

pgTextValue :: PGTextValue
 
PGBinaryValue

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

Fields

pgBinaryValue :: PGBinaryValue
 

type PGValues = [PGValue] Source

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

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. Nothing values represent unknown.

Constructors

PGTypeEnv 

Fields

pgIntegerDatetimes :: Maybe Bool

If integer_datetimes is on; only relevant for binary encoding.

Instances

newtype PGRecord Source

Generic class of composite (row or record) types.

Constructors

PGRecord [Maybe PGTextValue] 

Instances

PGRecordType t => PGColumn t PGRecord Source 
PGRecordType t => PGParameter t PGRecord Source 

Marshalling classes

class KnownSymbol t => PGType t where Source

A valid PostgreSQL type. This is just an indicator class: no implementation is needed. Unfortunately this will generate orphan instances wherever used.

Minimal complete definition

Nothing

Methods

pgTypeName :: PGTypeName t -> String Source

pgBinaryColumn :: PGTypeEnv -> PGTypeName t -> Bool Source

Does this type support binary decoding? If so, pgDecodeBinary must be implemented for every PGColumn instance of this type.

Instances

PGType "\"char\"" Source 
PGType "bigint" Source 
PGType "boolean" Source 
PGType "bpchar" Source 
PGType "bytea" Source 
PGType "character varying" Source 
PGType "date" Source 
PGType "double precision" Source 
PGType "integer" Source 
PGType "interval" Source 
PGType "json" Source 
PGType "jsonb" Source 
PGType "name" Source 
PGType "numeric" Source 
PGType "oid" Source 
PGType "real" Source 
PGType "record" Source 
PGType "smallint" Source 
PGType "text" Source 
PGType "time without time zone" Source 
PGType "timestamp with time zone" Source 
PGType "timestamp without time zone" Source 
PGType "uuid" Source 
PGType "void" Source 

class PGType 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 -> ByteString Source

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

pgEncodeValue :: PGTypeEnv -> PGTypeName t -> a -> PGValue Source

Encode a value to a PostgreSQL representation. Defaults to the text representation by pgEncode

Instances

PGRecordType t => PGParameter t PGRecord Source 
PGStringType t => PGParameter t Text Source 
PGStringType t => PGParameter t Text Source 
PGStringType t => PGParameter t ByteString Source 
PGStringType t => PGParameter t ByteString Source 
PGStringType t => PGParameter t String Source 
PGParameter "\"char\"" Char Source 
PGParameter "bigint" Int64 Source 
PGParameter "boolean" Bool Source 
PGParameter "bytea" ByteString Source 
PGParameter "bytea" ByteString Source 
PGParameter "cidr" PGInet Source 
PGParameter "date" Day Source 
PGParameter "double precision" Double Source 
PGParameter "inet" PGInet Source 
PGParameter "integer" Int32 Source 
PGParameter "interval" DiffTime Source 
PGParameter "json" Value Source 
PGParameter "jsonb" Value Source 
PGParameter "numeric" Rational Source 
PGParameter "numeric" Scientific Source 
PGParameter "oid" OID Source 
PGParameter "real" Float Source 
PGParameter "smallint" Int16 Source 
PGParameter "time without time zone" TimeOfDay Source 
PGParameter "timestamp with time zone" UTCTime Source 
PGParameter "timestamp without time zone" LocalTime Source 
PGParameter "uuid" UUID Source 
PGParameter t a => PGParameter t (Maybe a) Source 
(PGRangeType tr t, PGParameter t a) => PGParameter tr (Range a) Source 

class PGType t => PGColumn t a where Source

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

Minimal complete definition

pgDecode

Methods

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

Decode the PostgreSQL text representation into a value.

pgDecodeBinary :: PGTypeEnv -> PGTypeName t -> PGBinaryValue -> a Source

Decode the PostgreSQL binary representation into a value. Only needs to be implemented if pgBinaryColumn is true.

pgDecodeValue :: PGTypeEnv -> PGTypeName t -> PGValue -> a Source

Instances

PGRecordType t => PGColumn t PGRecord Source 
PGStringType t => PGColumn t Text Source 
PGStringType t => PGColumn t Text Source 
PGStringType t => PGColumn t ByteString Source 
PGStringType t => PGColumn t ByteString Source 
PGStringType t => PGColumn t String Source 
PGColumn "\"char\"" Char Source 
PGColumn "bigint" Int64 Source 
PGColumn "boolean" Bool Source 
PGColumn "bytea" ByteString Source 
PGColumn "bytea" ByteString Source 
PGColumn "date" Day Source 
PGColumn "double precision" Double Source 
PGColumn "integer" Int32 Source 
PGColumn "interval" DiffTime Source

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 "json" Value Source 
PGColumn "jsonb" Value Source 
PGColumn "numeric" Rational Source

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

PGColumn "numeric" Scientific Source 
PGColumn "oid" OID Source 
PGColumn "real" Float Source 
PGColumn "smallint" Int16 Source 
PGColumn "time without time zone" TimeOfDay Source 
PGColumn "timestamp with time zone" UTCTime Source 
PGColumn "timestamp without time zone" LocalTime Source 
PGColumn "uuid" UUID Source 
PGColumn "void" () Source 
PGColumn t a => PGColumn t (Maybe a) Source 
(PGRangeType tr t, PGColumn t a) => PGColumn tr (Range a) Source 

Marshalling interface

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

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

pgEscapeParameter :: PGParameter t a => PGTypeEnv -> PGTypeName t -> a -> ByteString Source

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

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

Final column decoding function used for a nullable result value.

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

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

Conversion utilities

pgQuote :: ByteString -> ByteString Source

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

pgDQuote :: [Char] -> ByteString -> Builder Source

Double-quote a value if it's "", "null", or contains any whitespace, '"', '\', or the characters given in the first argument. Checking all these things may not be worth it. We could just double-quote everything.

parsePGDQuote :: Bool -> [Char] -> (ByteString -> Bool) -> Parser (Maybe ByteString) Source

Parse double-quoted values ala pgDQuote.