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 PGTypeID t = PGTypeProxy
- data PGTypeEnv = PGTypeEnv {}
- unknownPGTypeEnv :: PGTypeEnv
- newtype PGName = PGName {
- pgNameBytes :: [Word8]
- pgNameBS :: PGName -> ByteString
- pgNameString :: PGName -> String
- newtype PGRecord = PGRecord [Maybe PGTextValue]
- class (KnownSymbol t, PGParameter t (PGVal t), PGColumn t (PGVal t)) => PGType t where
- class PGType t => PGParameter t a where
- class PGType t => PGColumn t a where
- class PGType t => PGStringType t
- class PGType t => PGRecordType t
- pgEncodeParameter :: PGParameter t a => PGTypeEnv -> PGTypeID t -> a -> PGValue
- pgEscapeParameter :: PGParameter t a => PGTypeEnv -> PGTypeID t -> a -> ByteString
- pgDecodeColumn :: PGColumn t (Maybe a) => PGTypeEnv -> PGTypeID t -> PGValue -> Maybe a
- pgDecodeColumnNotNull :: PGColumn t a => PGTypeEnv -> PGTypeID t -> PGValue -> a
- pgQuote :: ByteString -> ByteString
- pgDQuote :: [Char] -> ByteString -> Builder
- parsePGDQuote :: Bool -> [Char] -> (ByteString -> Bool) -> Parser (Maybe ByteString)
- 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.
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 |
Parameters that affect how marshalling happens. Currenly we force all other relevant parameters at connect time. Nothing values represent unknown.
Constructors
PGTypeEnv | |
Fields
|
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
pgNameBS :: PGName -> ByteString Source #
The literal identifier as used in a query.
Generic class of composite (row or record) types.
Instances
PGRecordType t => PGColumn t PGRecord Source # | |
PGRecordType t => PGParameter t PGRecord Source # | |
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.
Associated Types
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 # | |
PGType "any" 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 with time zone" 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
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
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 :: 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
class PGType t => PGStringType t Source #
Instances
PGStringType "bpchar" Source # | |
PGStringType "character varying" Source # | |
PGStringType "name" Source # | |
PGStringType "text" Source # | |
class PGType t => PGRecordType t Source #
Instances
PGRecordType "record" Source # | The generic anonymous record type, as created by |
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 :: [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
.
buildPGValue :: Builder -> ByteString Source #
Shorthand for toStrict
. toLazyByteString