postgresql-typed-0.4.5: A PostgreSQL library with compile-time SQL type inference and optional HDBC backend

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

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 

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

newtype PGRecord Source #

Generic class of composite (row or record) types.

Constructors

PGRecord [Maybe PGTextValue] 

Instances

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.

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 # 

Methods

pgTypeName :: PGTypeName "\"char\"" -> String Source #

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

PGType "any" Source # 
PGType "bigint" Source # 
PGType "boolean" Source # 
PGType "bpchar" Source # 
PGType "bytea" Source # 
PGType "character varying" Source # 

Methods

pgTypeName :: PGTypeName "character varying" -> String Source #

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

PGType "date" Source # 
PGType "double precision" Source # 

Methods

pgTypeName :: PGTypeName "double precision" -> String Source #

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

PGType "integer" Source # 
PGType "interval" Source # 

Methods

pgTypeName :: PGTypeName "interval" -> String Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeName "interval" -> Bool 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 # 

Methods

pgTypeName :: PGTypeName "smallint" -> String Source #

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

PGType "text" Source # 
PGType "time with time zone" Source # 

Methods

pgTypeName :: PGTypeName "time with time zone" -> String Source #

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

PGType "time without time zone" Source # 

Methods

pgTypeName :: PGTypeName "time without time zone" -> String Source #

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

PGType "timestamp with time zone" Source # 

Methods

pgTypeName :: PGTypeName "timestamp with time zone" -> String Source #

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

PGType "timestamp without time zone" Source # 

Methods

pgTypeName :: PGTypeName "timestamp without time zone" -> String Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeName "timestamp without time zone" -> Bool 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 # 

Methods

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

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

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

PGParameter "any" PGValue Source # 
PGParameter "bigint" Int64 Source # 

Methods

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

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

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

PGParameter "boolean" Bool Source # 

Methods

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

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

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

PGParameter "bytea" ByteString Source # 
PGParameter "bytea" ByteString Source # 
PGParameter "cidr" PGInet Source # 

Methods

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

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

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

PGParameter "date" Day Source # 

Methods

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

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

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

PGParameter "double precision" Double Source # 

Methods

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

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

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

PGParameter "double precision" Float Source # 

Methods

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

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

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

PGParameter "inet" PGInet Source # 

Methods

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

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

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

PGParameter "integer" Int32 Source # 

Methods

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

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

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

PGParameter "interval" DiffTime Source # 

Methods

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

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

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

PGParameter "json" Value Source # 

Methods

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

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

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

PGParameter "jsonb" Value Source # 

Methods

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

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

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

PGParameter "numeric" Rational Source # 

Methods

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

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

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

PGParameter "numeric" Scientific Source # 

Methods

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

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

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

PGParameter "oid" OID Source # 

Methods

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

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

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

PGParameter "real" Float Source # 

Methods

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

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

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

PGParameter "smallint" Int16 Source # 

Methods

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

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

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

PGParameter "time without time zone" TimeOfDay Source # 

Methods

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

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

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

PGParameter "timestamp with time zone" UTCTime Source # 

Methods

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

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

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

PGParameter "timestamp without time zone" LocalTime Source # 

Methods

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

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

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

PGParameter "uuid" UUID Source # 

Methods

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

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

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

PGParameter t a => PGParameter t (Maybe a) Source # 
(PGRangeType tr t, PGParameter t a) => PGParameter tr (Range a) Source # 
PGParameter "time with time zone" (TimeOfDay, TimeZone) Source # 

Methods

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

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

pgEncodeValue :: PGTypeEnv -> PGTypeName "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 :: 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 # 

Methods

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

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

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

PGStringType t => PGColumn t Text Source # 

Methods

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

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

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

PGStringType t => PGColumn t ByteString Source # 
PGStringType t => PGColumn t ByteString Source # 
PGStringType t => PGColumn t String Source # 

Methods

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

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

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

PGType t => PGColumn t PGValue Source # 
PGColumn "\"char\"" Char Source # 

Methods

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

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

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

PGColumn "bigint" Int64 Source # 

Methods

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

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

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

PGColumn "boolean" Bool Source # 

Methods

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

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

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

PGColumn "bytea" ByteString Source # 

Methods

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

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

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

PGColumn "bytea" ByteString Source # 

Methods

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

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

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

PGColumn "cidr" PGInet Source # 

Methods

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

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

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

PGColumn "date" Day Source # 

Methods

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

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

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

PGColumn "double precision" Double Source # 

Methods

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

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

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

PGColumn "inet" PGInet Source # 

Methods

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

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

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

PGColumn "integer" Int32 Source # 

Methods

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

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

pgDecodeValue :: PGTypeEnv -> PGTypeName "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

Methods

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

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

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

PGColumn "json" Value Source # 

Methods

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

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

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

PGColumn "jsonb" Value Source # 

Methods

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

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

pgDecodeValue :: PGTypeEnv -> PGTypeName "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.

Methods

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

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

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

PGColumn "numeric" Scientific Source # 

Methods

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

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

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

PGColumn "oid" OID Source # 

Methods

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

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

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

PGColumn "real" Double Source # 

Methods

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

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

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

PGColumn "real" Float Source # 

Methods

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

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

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

PGColumn "smallint" Int16 Source # 

Methods

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

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

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

PGColumn "time without time zone" TimeOfDay Source # 

Methods

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

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

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

PGColumn "timestamp with time zone" UTCTime Source # 

Methods

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

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

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

PGColumn "timestamp without time zone" LocalTime Source # 

Methods

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

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

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

PGColumn "uuid" UUID Source # 

Methods

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

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

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

PGColumn "void" () Source # 

Methods

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

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

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

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

Methods

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

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

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

(PGRangeType tr t, PGColumn t a) => PGColumn tr (Range a) Source # 

Methods

pgDecode :: PGTypeName tr -> PGTextValue -> Range a Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeName tr -> PGBinaryValue -> Range a Source #

pgDecodeValue :: PGTypeEnv -> PGTypeName tr -> PGValue -> Range a Source #

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

Methods

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

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

pgDecodeValue :: PGTypeEnv -> PGTypeName "time with time zone" -> PGValue -> (TimeOfDay, TimeZone) 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.