Copyright | 2015 Dylan Simon |
---|---|
Safe Haskell | None |
Language | Haskell98 |
Database.PostgreSQL.Typed.Types
Description
Classes to support type inference, value encoding/decoding, and instances to support built-in PostgreSQL types.
- type OID = Word32
- data PGValue
- = PGNullValue
- | PGTextValue {
- pgTextValue :: PGTextValue
- | PGBinaryValue {
- pgBinaryValue :: PGBinaryValue
- type PGValues = [PGValue]
- data PGTypeName t = PGTypeProxy
- data PGTypeEnv = PGTypeEnv {}
- unknownPGTypeEnv :: PGTypeEnv
- newtype PGRecord = PGRecord [Maybe PGTextValue]
- class KnownSymbol t => PGType t where
- pgTypeName :: PGTypeName t -> String
- pgBinaryColumn :: PGTypeEnv -> PGTypeName t -> Bool
- class PGType t => PGParameter t a where
- pgEncode :: PGTypeName t -> a -> PGTextValue
- pgLiteral :: PGTypeName t -> a -> String
- pgEncodeValue :: PGTypeEnv -> PGTypeName t -> a -> PGValue
- class PGType t => PGColumn t a where
- pgDecode :: PGTypeName t -> PGTextValue -> a
- pgDecodeBinary :: PGTypeEnv -> PGTypeName t -> PGBinaryValue -> a
- pgDecodeValue :: PGTypeEnv -> PGTypeName t -> PGValue -> a
- pgEncodeParameter :: PGParameter t a => PGTypeEnv -> PGTypeName t -> a -> PGValue
- pgEscapeParameter :: PGParameter t a => PGTypeEnv -> PGTypeName t -> a -> String
- pgDecodeColumn :: PGColumn t (Maybe a) => PGTypeEnv -> PGTypeName t -> PGValue -> Maybe a
- pgDecodeColumnNotNull :: PGColumn t a => PGTypeEnv -> PGTypeName t -> PGValue -> a
- pgQuote :: String -> String
- pgDQuote :: String -> ByteString -> Builder
- parsePGDQuote :: Stream s m Char => String -> (String -> Bool) -> ParsecT s u m (Maybe String)
- buildPGValue :: Builder -> ByteString
Basic types
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 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 |
Parameters that affect how marshalling happens. Currenly we force all other relevant parameters at connect time. Nothing values represent unknown.
Constructors
PGTypeEnv | |
Fields
|
Generic class of composite (row or record) types.
Instances
PGRecordType t => PGColumn t PGRecord | |
PGRecordType t => PGParameter t PGRecord |
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\"" | |
PGType "\"char\"" => PGType "\"char\"[]" | |
PGType "abstime" => PGType "abstime[]" | |
PGType "aclitem" => PGType "aclitem[]" | |
PGType "bigint" | |
PGType "bigint" => PGType "bigint[]" | |
PGType "bit" => PGType "bit[]" | |
PGType "boolean" | |
PGType "boolean" => PGType "boolean[]" | |
PGType "box" => PGType "box[]" | |
PGType "bpchar" | |
PGType "bpchar" => PGType "bpchar[]" | |
PGType "bytea" | |
PGType "bytea" => PGType "bytea[]" | |
PGType "character varying" | |
PGType "character varying" => PGType "character varying[]" | |
PGType "cid" => PGType "cid[]" | |
PGType "cidr" | |
PGType "cidr" => PGType "cidr[]" | |
PGType "circle" => PGType "circle[]" | |
PGType "cstring" => PGType "cstring[]" | |
PGType "date" | |
PGType "date" => PGType "date[]" | |
PGType "daterange" | |
PGType "daterange" => PGType "daterange[]" | |
PGType "double precision" | |
PGType "double precision" => PGType "double precision[]" | |
PGType "gtsvector" => PGType "gtsvector[]" | |
PGType "inet" | |
PGType "inet" => PGType "inet[]" | |
PGType "int2vector" => PGType "int2vector[]" | |
PGType "int4range" | |
PGType "int4range" => PGType "int4range[]" | |
PGType "int8range" | |
PGType "int8range" => PGType "int8range[]" | |
PGType "integer" | |
PGType "integer" => PGType "integer[]" | |
PGType "interval" | |
PGType "interval" => PGType "interval[]" | |
PGType "json" | |
PGType "json" => PGType "json[]" | |
PGType "jsonb" | |
PGType "line" => PGType "line[]" | |
PGType "lseg" => PGType "lseg[]" | |
PGType "macaddr" => PGType "macaddr[]" | |
PGType "money" => PGType "money[]" | |
PGType "name" | |
PGType "name" => PGType "name[]" | |
PGType "numeric" | |
PGType "numeric" => PGType "numeric[]" | |
PGType "numrange" | |
PGType "numrange" => PGType "numrange[]" | |
PGType "oid" | |
PGType "oid" => PGType "oid[]" | |
PGType "oidvector" => PGType "oidvector[]" | |
PGType "path" => PGType "path[]" | |
PGType "point" => PGType "point[]" | |
PGType "polygon" => PGType "polygon[]" | |
PGType "real" | |
PGType "real" => PGType "real[]" | |
PGType "record" | |
PGType "record" => PGType "record[]" | |
PGType "refcursor" => PGType "refcursor[]" | |
PGType "regclass" => PGType "regclass[]" | |
PGType "regconfig" => PGType "regconfig[]" | |
PGType "regdictionary" => PGType "regdictionary[]" | |
PGType "regoper" => PGType "regoper[]" | |
PGType "regoperator" => PGType "regoperator[]" | |
PGType "regproc" => PGType "regproc[]" | |
PGType "regprocedure" => PGType "regprocedure[]" | |
PGType "regtype" => PGType "regtype[]" | |
PGType "reltime" => PGType "reltime[]" | |
PGType "smallint" | |
PGType "smallint" => PGType "smallint[]" | |
PGType "text" | |
PGType "text" => PGType "text[]" | |
PGType "tid" => PGType "tid[]" | |
PGType "time with time zone" => PGType "time with time zone[]" | |
PGType "time without time zone" | |
PGType "time without time zone" => PGType "time without time zone[]" | |
PGType "timestamp with time zone" | |
PGType "timestamp with time zone" => PGType "timestamp with time zone[]" | |
PGType "timestamp without time zone" | |
PGType "timestamp without time zone" => PGType "timestamp without time zone[]" | |
PGType "tinterval" => PGType "tinterval[]" | |
PGType "tsquery" => PGType "tsquery[]" | |
PGType "tsrange" | |
PGType "tsrange" => PGType "tsrange[]" | |
PGType "tstzrange" | |
PGType "tstzrange" => PGType "tstzrange[]" | |
PGType "tsvector" => PGType "tsvector[]" | |
PGType "txid_snapshot" => PGType "txid_snapshot[]" | |
PGType "uuid" | |
PGType "uuid" => PGType "uuid[]" | |
PGType "varbit" => PGType "varbit[]" | |
PGType "void" | |
PGType "xid" => PGType "xid[]" | |
PGType "xml" => PGType "xml[]" |
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
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
pgEncodeValue :: PGTypeEnv -> PGTypeName t -> a -> PGValue Source
Encode a value to a PostgreSQL representation. Defaults to the text representation by pgEncode
Instances
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
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 | |
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 | |
PGColumn "\"char\"" Char | |
PGColumn "bigint" Int64 | |
PGColumn "boolean" Bool | |
PGColumn "bytea" ByteString | |
PGColumn "bytea" ByteString | |
PGColumn "date" Day | |
PGColumn "double precision" Double | |
PGColumn "integer" Int32 | |
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 "json" Value | |
PGColumn "jsonb" Value | |
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 "numeric" Scientific | |
PGColumn "oid" OID | |
PGColumn "real" Float | |
PGColumn "smallint" Int16 | |
PGColumn "time without time zone" TimeOfDay | |
PGColumn "timestamp with time zone" UTCTime | |
PGColumn "timestamp without time zone" LocalTime | |
PGColumn "uuid" UUID | |
PGColumn "void" () | |
PGColumn t a => PGColumn t (Maybe a) | |
(PGArrayType ta t, PGColumn t a) => PGColumn ta (PGArray a) | |
(PGRangeType tr t, PGColumn t a) => PGColumn tr (Range a) |
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 -> String 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 :: String -> String Source
Produce a SQL string literal by wrapping (and escaping) a string with single quotes.
pgDQuote :: String -> 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 :: Stream s m Char => String -> (String -> Bool) -> ParsecT s u m (Maybe String) Source
Parse double-quoted values ala pgDQuote
.
buildPGValue :: Builder -> ByteString Source