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

Copyright2015 Dylan Simon
Safe HaskellNone
LanguageHaskell2010

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

PGBinaryValue

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

Fields

type PGValues = [PGValue] Source #

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

data PGTypeID (t :: Symbol) Source #

A proxy type for PostgreSQL types. The type argument should be an (internal) name of a database type, as per format_type(OID) (usually the same as \dT+). When the type's namespace (schema) is not in search_path, this will be explicitly qualified, so you should be sure to have a consistent search_path for all database connections. The underlying Symbol should be considered a lifted PGName.

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

Instances
Show PGTypeEnv Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

newtype PGName Source #

A PostgreSQL literal identifier, generally corresponding to the "name" type (63-byte strings), but as it would be entered in a query, so may include double-quoting for special characters or schema-qualification.

Constructors

PGName 

Fields

Instances
Eq PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

(==) :: PGName -> PGName -> Bool #

(/=) :: PGName -> PGName -> Bool #

Data PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PGName -> c PGName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PGName #

toConstr :: PGName -> Constr #

dataTypeOf :: PGName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PGName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PGName) #

gmapT :: (forall b. Data b => b -> b) -> PGName -> PGName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PGName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PGName -> r #

gmapQ :: (forall d. Data d => d -> u) -> PGName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PGName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PGName -> m PGName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PGName -> m PGName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PGName -> m PGName #

Ord PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Show PGName Source #

Unquoted pgNameString.

Instance details

Defined in Database.PostgreSQL.Typed.Types

IsString PGName Source #

Applies utf-8 encoding.

Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

fromString :: String -> PGName #

PGRep PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Dynamic

Associated Types

type PGRepType PGName :: Symbol Source #

PGStringType t => PGColumn t PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGName Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGName Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGName Source #

PGStringType t => PGParameter t PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

type PGRepType PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Dynamic

type PGRepType PGName = "text"

pgNameBS :: PGName -> ByteString Source #

The literal identifier as used in a query.

pgNameString :: PGName -> String Source #

Reverses the IsString instantce.

newtype PGRecord Source #

Generic class of composite (row or record) types.

Constructors

PGRecord [Maybe PGTextValue] 

Marshalling classes

class (KnownSymbol t, PGParameter t (PGVal t), PGColumn t (PGVal t)) => PGType t where Source #

A valid PostgreSQL type, its metadata, and corresponding Haskell representation. For conversion the other way (from Haskell type to PostgreSQL), see PGRep. Unfortunately any instances of this will be orphans.

Minimal complete definition

Nothing

Associated Types

type PGVal t :: * Source #

The default, native Haskell representation of this type, which should be as close as possible to the PostgreSQL representation.

Methods

pgTypeName :: PGTypeID t -> PGName Source #

The string name of this type: specialized version of symbolVal.

pgBinaryColumn :: PGTypeEnv -> PGTypeID 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 # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "\"char\"" :: Type Source #

Methods

pgTypeName :: PGTypeID "\"char\"" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "\"char\"" -> Bool Source #

PGType "\"char\"" => PGType "\"char\"[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "\"char\"[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "\"char\"[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "\"char\"[]" -> Bool Source #

PGType "abstime" => PGType "abstime[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "abstime[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "abstime[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "abstime[]" -> Bool Source #

PGType "aclitem" => PGType "aclitem[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "aclitem[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "aclitem[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "aclitem[]" -> Bool Source #

PGType "any" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "any" :: Type Source #

PGType "bigint" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "bigint" :: Type Source #

Methods

pgTypeName :: PGTypeID "bigint" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "bigint" -> Bool Source #

PGType "bigint" => PGType "bigint[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "bigint[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "bigint[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "bigint[]" -> Bool Source #

PGType "bit" => PGType "bit[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "bit[]" :: Type Source #

PGType "boolean" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "boolean" :: Type Source #

Methods

pgTypeName :: PGTypeID "boolean" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "boolean" -> Bool Source #

PGType "boolean" => PGType "boolean[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "boolean[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "boolean[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "boolean[]" -> Bool Source #

PGType "box" => PGType "box[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "box[]" :: Type Source #

PGType "bpchar" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "bpchar" :: Type Source #

Methods

pgTypeName :: PGTypeID "bpchar" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "bpchar" -> Bool Source #

PGType "bpchar" => PGType "bpchar[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "bpchar[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "bpchar[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "bpchar[]" -> Bool Source #

PGType "bytea" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "bytea" :: Type Source #

PGType "bytea" => PGType "bytea[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "bytea[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "bytea[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "bytea[]" -> Bool Source #

PGType "character varying" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "character varying" :: Type Source #

Methods

pgTypeName :: PGTypeID "character varying" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "character varying" -> Bool Source #

PGType "character varying" => PGType "character varying[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "character varying[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "character varying[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "character varying[]" -> Bool Source #

PGType "cid" => PGType "cid[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "cid[]" :: Type Source #

PGType "cidr" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Inet

Associated Types

type PGVal "cidr" :: Type Source #

PGType "cidr" => PGType "cidr[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "cidr[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "cidr[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "cidr[]" -> Bool Source #

PGType "circle" => PGType "circle[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "circle[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "circle[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "circle[]" -> Bool Source #

PGType "cstring" => PGType "cstring[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "cstring[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "cstring[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "cstring[]" -> Bool Source #

PGType "date" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "date" :: Type Source #

PGType "date" => PGType "date[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "date[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "date[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "date[]" -> Bool Source #

PGType "daterange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGVal "daterange" :: Type Source #

Methods

pgTypeName :: PGTypeID "daterange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "daterange" -> Bool Source #

PGType "daterange" => PGType "daterange[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "daterange[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "daterange[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "daterange[]" -> Bool Source #

PGType "double precision" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "double precision" :: Type Source #

Methods

pgTypeName :: PGTypeID "double precision" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "double precision" -> Bool Source #

PGType "double precision" => PGType "double precision[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "double precision[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "double precision[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "double precision[]" -> Bool Source #

PGType "gtsvector" => PGType "gtsvector[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "gtsvector[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "gtsvector[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "gtsvector[]" -> Bool Source #

PGType "inet" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Inet

Associated Types

type PGVal "inet" :: Type Source #

PGType "inet" => PGType "inet[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "inet[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "inet[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "inet[]" -> Bool Source #

PGType "int2vector" => PGType "int2vector[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "int2vector[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "int2vector[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int2vector[]" -> Bool Source #

PGType "int4range" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGVal "int4range" :: Type Source #

Methods

pgTypeName :: PGTypeID "int4range" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int4range" -> Bool Source #

PGType "int4range" => PGType "int4range[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "int4range[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "int4range[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int4range[]" -> Bool Source #

PGType "int8range" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGVal "int8range" :: Type Source #

Methods

pgTypeName :: PGTypeID "int8range" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int8range" -> Bool Source #

PGType "int8range" => PGType "int8range[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "int8range[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "int8range[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int8range[]" -> Bool Source #

PGType "integer" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "integer" :: Type Source #

Methods

pgTypeName :: PGTypeID "integer" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "integer" -> Bool Source #

PGType "integer" => PGType "integer[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "integer[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "integer[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "integer[]" -> Bool Source #

PGType "interval" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "interval" :: Type Source #

Methods

pgTypeName :: PGTypeID "interval" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "interval" -> Bool Source #

PGType "interval" => PGType "interval[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "interval[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "interval[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "interval[]" -> Bool Source #

PGType "json" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "json" :: Type Source #

PGType "json" => PGType "json[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "json[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "json[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "json[]" -> Bool Source #

PGType "jsonb" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "jsonb" :: Type Source #

PGType "line" => PGType "line[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "line[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "line[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "line[]" -> Bool Source #

PGType "lseg" => PGType "lseg[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "lseg[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "lseg[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "lseg[]" -> Bool Source #

PGType "macaddr" => PGType "macaddr[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "macaddr[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "macaddr[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "macaddr[]" -> Bool Source #

PGType "money" => PGType "money[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "money[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "money[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "money[]" -> Bool Source #

PGType "name" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "name" :: Type Source #

PGType "name" => PGType "name[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "name[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "name[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "name[]" -> Bool Source #

PGType "numeric" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "numeric" :: Type Source #

Methods

pgTypeName :: PGTypeID "numeric" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "numeric" -> Bool Source #

PGType "numeric" => PGType "numeric[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "numeric[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "numeric[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "numeric[]" -> Bool Source #

PGType "numrange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGVal "numrange" :: Type Source #

Methods

pgTypeName :: PGTypeID "numrange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "numrange" -> Bool Source #

PGType "numrange" => PGType "numrange[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "numrange[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "numrange[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "numrange[]" -> Bool Source #

PGType "oid" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "oid" :: Type Source #

PGType "oid" => PGType "oid[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "oid[]" :: Type Source #

PGType "oidvector" => PGType "oidvector[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "oidvector[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "oidvector[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "oidvector[]" -> Bool Source #

PGType "path" => PGType "path[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "path[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "path[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "path[]" -> Bool Source #

PGType "point" => PGType "point[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "point[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "point[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "point[]" -> Bool Source #

PGType "polygon" => PGType "polygon[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "polygon[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "polygon[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "polygon[]" -> Bool Source #

PGType "real" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "real" :: Type Source #

PGType "real" => PGType "real[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "real[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "real[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "real[]" -> Bool Source #

PGType "record" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "record" :: Type Source #

Methods

pgTypeName :: PGTypeID "record" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "record" -> Bool Source #

PGType "record" => PGType "record[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "record[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "record[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "record[]" -> Bool Source #

PGType "refcursor" => PGType "refcursor[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "refcursor[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "refcursor[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "refcursor[]" -> Bool Source #

PGType "regclass" => PGType "regclass[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regclass[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regclass[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regclass[]" -> Bool Source #

PGType "regconfig" => PGType "regconfig[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regconfig[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regconfig[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regconfig[]" -> Bool Source #

PGType "regdictionary" => PGType "regdictionary[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regdictionary[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regdictionary[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regdictionary[]" -> Bool Source #

PGType "regoper" => PGType "regoper[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regoper[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regoper[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regoper[]" -> Bool Source #

PGType "regoperator" => PGType "regoperator[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regoperator[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regoperator[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regoperator[]" -> Bool Source #

PGType "regproc" => PGType "regproc[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regproc[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regproc[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regproc[]" -> Bool Source #

PGType "regprocedure" => PGType "regprocedure[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regprocedure[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regprocedure[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regprocedure[]" -> Bool Source #

PGType "regtype" => PGType "regtype[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "regtype[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "regtype[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "regtype[]" -> Bool Source #

PGType "reltime" => PGType "reltime[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "reltime[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "reltime[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "reltime[]" -> Bool Source #

PGType "smallint" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "smallint" :: Type Source #

Methods

pgTypeName :: PGTypeID "smallint" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "smallint" -> Bool Source #

PGType "smallint" => PGType "smallint[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "smallint[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "smallint[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "smallint[]" -> Bool Source #

PGType "text" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "text" :: Type Source #

PGType "text" => PGType "text[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "text[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "text[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "text[]" -> Bool Source #

PGType "tid" => PGType "tid[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "tid[]" :: Type Source #

PGType "time with time zone" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "time with time zone" :: Type Source #

Methods

pgTypeName :: PGTypeID "time with time zone" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "time with time zone" -> Bool Source #

PGType "time with time zone" => PGType "time with time zone[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "time with time zone[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "time with time zone[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "time with time zone[]" -> Bool Source #

PGType "time without time zone" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "time without time zone" :: Type Source #

Methods

pgTypeName :: PGTypeID "time without time zone" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "time without time zone" -> Bool Source #

PGType "time without time zone" => PGType "time without time zone[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "time without time zone[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "time without time zone[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "time without time zone[]" -> Bool Source #

PGType "timestamp with time zone" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "timestamp with time zone" :: Type Source #

Methods

pgTypeName :: PGTypeID "timestamp with time zone" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> Bool Source #

PGType "timestamp with time zone" => PGType "timestamp with time zone[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "timestamp with time zone[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "timestamp with time zone[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "timestamp with time zone[]" -> Bool Source #

PGType "timestamp without time zone" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "timestamp without time zone" :: Type Source #

Methods

pgTypeName :: PGTypeID "timestamp without time zone" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> Bool Source #

PGType "timestamp without time zone" => PGType "timestamp without time zone[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "timestamp without time zone[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "timestamp without time zone[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "timestamp without time zone[]" -> Bool Source #

PGType "tinterval" => PGType "tinterval[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "tinterval[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "tinterval[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tinterval[]" -> Bool Source #

PGType "tsquery" => PGType "tsquery[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "tsquery[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "tsquery[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tsquery[]" -> Bool Source #

PGType "tsrange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGVal "tsrange" :: Type Source #

Methods

pgTypeName :: PGTypeID "tsrange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tsrange" -> Bool Source #

PGType "tsrange" => PGType "tsrange[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "tsrange[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "tsrange[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tsrange[]" -> Bool Source #

PGType "tstzrange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGVal "tstzrange" :: Type Source #

Methods

pgTypeName :: PGTypeID "tstzrange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tstzrange" -> Bool Source #

PGType "tstzrange" => PGType "tstzrange[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "tstzrange[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "tstzrange[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tstzrange[]" -> Bool Source #

PGType "tsvector" => PGType "tsvector[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "tsvector[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "tsvector[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tsvector[]" -> Bool Source #

PGType "txid_snapshot" => PGType "txid_snapshot[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "txid_snapshot[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "txid_snapshot[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "txid_snapshot[]" -> Bool Source #

PGType "uuid" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "uuid" :: Type Source #

PGType "uuid" => PGType "uuid[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "uuid[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "uuid[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "uuid[]" -> Bool Source #

PGType "varbit" => PGType "varbit[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "varbit[]" :: Type Source #

Methods

pgTypeName :: PGTypeID "varbit[]" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "varbit[]" -> Bool Source #

PGType "void" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Associated Types

type PGVal "void" :: Type Source #

PGType "xid" => PGType "xid[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "xid[]" :: Type Source #

PGType "xml" => PGType "xml[]" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Associated Types

type PGVal "xml[]" :: Type 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 :: PGTypeID t -> a -> PGTextValue Source #

Encode a value to a PostgreSQL text representation.

pgLiteral :: PGTypeID 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 -> PGTypeID 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 # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t Text Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t Text Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t String Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGParameter "\"char\"" Char Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "\"char\"" -> Char -> PGTextValue Source #

pgLiteral :: PGTypeID "\"char\"" -> Char -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> Char -> PGValue Source #

PGParameter "\"char\"" Word8 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "\"char\"" -> Word8 -> PGTextValue Source #

pgLiteral :: PGTypeID "\"char\"" -> Word8 -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> Word8 -> PGValue Source #

PGParameter "any" PGValue Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "any" -> PGValue -> PGTextValue Source #

pgLiteral :: PGTypeID "any" -> PGValue -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "any" -> PGValue -> PGValue Source #

PGParameter "bigint" Int64 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "bigint" -> Int64 -> PGTextValue Source #

pgLiteral :: PGTypeID "bigint" -> Int64 -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "bigint" -> Int64 -> PGValue Source #

PGParameter "boolean" Bool Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "boolean" -> Bool -> PGTextValue Source #

pgLiteral :: PGTypeID "boolean" -> Bool -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "boolean" -> Bool -> PGValue Source #

PGParameter "bytea" ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "bytea" -> ByteString -> PGTextValue Source #

pgLiteral :: PGTypeID "bytea" -> ByteString -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "bytea" -> ByteString -> PGValue Source #

PGParameter "bytea" ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "bytea" -> ByteString -> PGTextValue Source #

pgLiteral :: PGTypeID "bytea" -> ByteString -> ByteString0 Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "bytea" -> ByteString -> PGValue Source #

PGParameter "cidr" PGInet Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Inet

Methods

pgEncode :: PGTypeID "cidr" -> PGInet -> PGTextValue Source #

pgLiteral :: PGTypeID "cidr" -> PGInet -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "cidr" -> PGInet -> PGValue Source #

PGParameter "date" Day Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "date" -> Day -> PGTextValue Source #

pgLiteral :: PGTypeID "date" -> Day -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "date" -> Day -> PGValue Source #

PGParameter "double precision" Double Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "double precision" -> Double -> PGTextValue Source #

pgLiteral :: PGTypeID "double precision" -> Double -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "double precision" -> Double -> PGValue Source #

PGParameter "double precision" Float Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "double precision" -> Float -> PGTextValue Source #

pgLiteral :: PGTypeID "double precision" -> Float -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "double precision" -> Float -> PGValue Source #

PGParameter "inet" PGInet Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Inet

Methods

pgEncode :: PGTypeID "inet" -> PGInet -> PGTextValue Source #

pgLiteral :: PGTypeID "inet" -> PGInet -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "inet" -> PGInet -> PGValue Source #

PGParameter "integer" Int32 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "integer" -> Int32 -> PGTextValue Source #

pgLiteral :: PGTypeID "integer" -> Int32 -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "integer" -> Int32 -> PGValue Source #

PGParameter "interval" DiffTime Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "interval" -> DiffTime -> PGTextValue Source #

pgLiteral :: PGTypeID "interval" -> DiffTime -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "interval" -> DiffTime -> PGValue Source #

PGParameter "json" Value Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "json" -> Value -> PGTextValue Source #

pgLiteral :: PGTypeID "json" -> Value -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "json" -> Value -> PGValue Source #

PGParameter "jsonb" Value Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "jsonb" -> Value -> PGTextValue Source #

pgLiteral :: PGTypeID "jsonb" -> Value -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "jsonb" -> Value -> PGValue Source #

PGParameter "numeric" Rational Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "numeric" -> Rational -> PGTextValue Source #

pgLiteral :: PGTypeID "numeric" -> Rational -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "numeric" -> Rational -> PGValue Source #

PGParameter "numeric" Scientific Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "numeric" -> Scientific -> PGTextValue Source #

pgLiteral :: PGTypeID "numeric" -> Scientific -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "numeric" -> Scientific -> PGValue Source #

PGParameter "oid" OID Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "oid" -> OID -> PGTextValue Source #

pgLiteral :: PGTypeID "oid" -> OID -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "oid" -> OID -> PGValue Source #

PGParameter "real" Float Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "real" -> Float -> PGTextValue Source #

pgLiteral :: PGTypeID "real" -> Float -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "real" -> Float -> PGValue Source #

PGParameter "smallint" Int16 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "smallint" -> Int16 -> PGTextValue Source #

pgLiteral :: PGTypeID "smallint" -> Int16 -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "smallint" -> Int16 -> PGValue Source #

PGParameter "time without time zone" TimeOfDay Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "time without time zone" -> TimeOfDay -> PGTextValue Source #

pgLiteral :: PGTypeID "time without time zone" -> TimeOfDay -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "time without time zone" -> TimeOfDay -> PGValue Source #

PGParameter "timestamp with time zone" UTCTime Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "timestamp with time zone" -> UTCTime -> PGTextValue Source #

pgLiteral :: PGTypeID "timestamp with time zone" -> UTCTime -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> UTCTime -> PGValue Source #

PGParameter "timestamp without time zone" LocalTime Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "timestamp without time zone" -> LocalTime -> PGTextValue Source #

pgLiteral :: PGTypeID "timestamp without time zone" -> LocalTime -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> LocalTime -> PGValue Source #

PGParameter "uuid" UUID Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "uuid" -> UUID -> PGTextValue Source #

pgLiteral :: PGTypeID "uuid" -> UUID -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "uuid" -> UUID -> PGValue Source #

PGParameter "void" () Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "void" -> () -> PGTextValue Source #

pgLiteral :: PGTypeID "void" -> () -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "void" -> () -> PGValue Source #

PGParameter t a => PGParameter t (Maybe a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

(PGRangeType t, PGParameter (PGSubType t) a) => PGParameter t (Range a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

(PGArrayType t, PGParameter (PGElemType t) a) => PGParameter t [a] Source #

Allow entirely non-null arrays as parameter inputs only. (Only supported on ghc >= 7.10 due to instance overlap.)

Instance details

Defined in Database.PostgreSQL.Typed.Array

Methods

pgEncode :: PGTypeID t -> [a] -> PGTextValue Source #

pgLiteral :: PGTypeID t -> [a] -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID t -> [a] -> PGValue Source #

(PGArrayType t, PGParameter (PGElemType t) a) => PGParameter t (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

PGParameter "time with time zone" (TimeOfDay, TimeZone) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "time with time zone" -> (TimeOfDay, TimeZone) -> PGTextValue Source #

pgLiteral :: PGTypeID "time with time zone" -> (TimeOfDay, TimeZone) -> ByteString Source #

pgEncodeValue :: PGTypeEnv -> PGTypeID "time with time zone" -> (TimeOfDay, TimeZone) -> PGValue 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 :: PGTypeID t -> PGTextValue -> a Source #

Decode the PostgreSQL text representation into a value.

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> a Source #

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

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> a Source #

Instances
PGRecordType t => PGColumn t PGRecord Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGRecord Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGRecord Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGRecord Source #

PGStringType t => PGColumn t Text Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Text Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Text Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Text Source #

PGStringType t => PGColumn t Text Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Text Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Text Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Text Source #

PGStringType t => PGColumn t ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGColumn t PGName Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGName Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGName Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGName Source #

PGStringType t => PGColumn t ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGColumn t String Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> String Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> String Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> String Source #

PGType t => PGColumn t PGValue Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGValue Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGValue Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGValue Source #

PGColumn "\"char\"" Char Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "\"char\"" -> PGTextValue -> Char Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "\"char\"" -> PGBinaryValue -> Char Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> PGValue -> Char Source #

PGColumn "\"char\"" Word8 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "\"char\"" -> PGTextValue -> Word8 Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "\"char\"" -> PGBinaryValue -> Word8 Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> PGValue -> Word8 Source #

PGColumn "bigint" Int64 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "bigint" -> PGTextValue -> Int64 Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "bigint" -> PGBinaryValue -> Int64 Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "bigint" -> PGValue -> Int64 Source #

PGColumn "boolean" Bool Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "boolean" -> PGTextValue -> Bool Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "boolean" -> PGBinaryValue -> Bool Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "boolean" -> PGValue -> Bool Source #

PGColumn "bytea" ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "bytea" -> PGTextValue -> ByteString Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "bytea" -> PGBinaryValue -> ByteString Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "bytea" -> PGValue -> ByteString Source #

PGColumn "bytea" ByteString Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "bytea" -> PGTextValue -> ByteString Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "bytea" -> PGBinaryValue -> ByteString Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "bytea" -> PGValue -> ByteString Source #

PGColumn "cidr" PGInet Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Inet

Methods

pgDecode :: PGTypeID "cidr" -> PGTextValue -> PGInet Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "cidr" -> PGBinaryValue -> PGInet Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "cidr" -> PGValue -> PGInet Source #

PGColumn "date" Day Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "date" -> PGTextValue -> Day Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "date" -> PGBinaryValue -> Day Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "date" -> PGValue -> Day Source #

PGColumn "double precision" Double Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "double precision" -> PGTextValue -> Double Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "double precision" -> PGBinaryValue -> Double Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "double precision" -> PGValue -> Double Source #

PGColumn "inet" PGInet Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Inet

Methods

pgDecode :: PGTypeID "inet" -> PGTextValue -> PGInet Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "inet" -> PGBinaryValue -> PGInet Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "inet" -> PGValue -> PGInet Source #

PGColumn "integer" Int32 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "integer" -> PGTextValue -> Int32 Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "integer" -> PGBinaryValue -> Int32 Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "integer" -> PGValue -> 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

Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "interval" -> PGTextValue -> DiffTime Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "interval" -> PGBinaryValue -> DiffTime Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "interval" -> PGValue -> DiffTime Source #

PGColumn "json" Value Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "json" -> PGTextValue -> Value Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "json" -> PGBinaryValue -> Value Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "json" -> PGValue -> Value Source #

PGColumn "jsonb" Value Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "jsonb" -> PGTextValue -> Value Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "jsonb" -> PGBinaryValue -> Value Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "jsonb" -> PGValue -> 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.

Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "numeric" -> PGTextValue -> Rational Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "numeric" -> PGBinaryValue -> Rational Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "numeric" -> PGValue -> Rational Source #

PGColumn "numeric" Scientific Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "numeric" -> PGTextValue -> Scientific Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "numeric" -> PGBinaryValue -> Scientific Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "numeric" -> PGValue -> Scientific Source #

PGColumn "oid" OID Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "oid" -> PGTextValue -> OID Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "oid" -> PGBinaryValue -> OID Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "oid" -> PGValue -> OID Source #

PGColumn "real" Double Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "real" -> PGTextValue -> Double Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "real" -> PGBinaryValue -> Double Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "real" -> PGValue -> Double Source #

PGColumn "real" Float Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "real" -> PGTextValue -> Float Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "real" -> PGBinaryValue -> Float Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "real" -> PGValue -> Float Source #

PGColumn "smallint" Int16 Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "smallint" -> PGTextValue -> Int16 Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "smallint" -> PGBinaryValue -> Int16 Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "smallint" -> PGValue -> Int16 Source #

PGColumn "time without time zone" TimeOfDay Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "time without time zone" -> PGTextValue -> TimeOfDay Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "time without time zone" -> PGBinaryValue -> TimeOfDay Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "time without time zone" -> PGValue -> TimeOfDay Source #

PGColumn "timestamp with time zone" UTCTime Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "timestamp with time zone" -> PGTextValue -> UTCTime Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> PGBinaryValue -> UTCTime Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> PGValue -> UTCTime Source #

PGColumn "timestamp without time zone" LocalTime Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "timestamp without time zone" -> PGTextValue -> LocalTime Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> PGBinaryValue -> LocalTime Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> PGValue -> LocalTime Source #

PGColumn "uuid" UUID Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "uuid" -> PGTextValue -> UUID Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "uuid" -> PGBinaryValue -> UUID Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "uuid" -> PGValue -> UUID Source #

PGColumn "void" () Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "void" -> PGTextValue -> () Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "void" -> PGBinaryValue -> () Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "void" -> PGValue -> () Source #

PGColumn t a => PGColumn t (Maybe a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Maybe a Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Maybe a Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Maybe a Source #

(PGRangeType t, PGColumn (PGSubType t) a) => PGColumn t (Range a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Range a Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Range a Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Range a Source #

(PGArrayType t, PGColumn (PGElemType t) a) => PGColumn t (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Array

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGArray a Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGArray a Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGArray a Source #

PGColumn "time with time zone" (TimeOfDay, TimeZone) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "time with time zone" -> PGTextValue -> (TimeOfDay, TimeZone) Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "time with time zone" -> PGBinaryValue -> (TimeOfDay, TimeZone) Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID "time with time zone" -> PGValue -> (TimeOfDay, TimeZone) Source #

class PGType t => PGStringType t Source #

Instances
PGStringType "bpchar" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType "character varying" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType "name" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType "text" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Types

class PGType t => PGRecordType t Source #

Instances
PGRecordType "record" Source #

The generic anonymous record type, as created by ROW. In this case we can not know the types, and in fact, PostgreSQL does not accept values of this type regardless (except as literals).

Instance details

Defined in Database.PostgreSQL.Typed.Types

Marshalling interface

pgEncodeParameter :: PGParameter t a => PGTypeEnv -> PGTypeID t -> a -> PGValue Source #

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

pgEscapeParameter :: PGParameter t a => PGTypeEnv -> PGTypeID 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 -> PGTypeID t -> PGValue -> Maybe a Source #

Final column decoding function used for a nullable result value.

pgDecodeColumnNotNull :: PGColumn t a => PGTypeEnv -> PGTypeID 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 :: ByteString -> Builder Source #

Double-quote a value (e.g., as an identifier). Does not properly handle unicode escaping (yet).

pgDQuoteFrom :: [Char] -> ByteString -> Builder Source #

Double-quote a value if it's "", "null", or contains any whitespace, '"', '\', or the characters given in the first argument.

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

Parse double-quoted values ala pgDQuote.