Copyright | 2015 Dylan Simon |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Classes to support type inference, value encoding/decoding, and instances to support built-in PostgreSQL types.
Synopsis
- type OID = Word32
- data PGValue
- = PGNullValue
- | PGTextValue {
- pgTextValue :: PGTextValue
- | PGBinaryValue {
- pgBinaryValue :: PGBinaryValue
- type PGValues = [PGValue]
- data PGTypeID (t :: Symbol) = 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
- type PGVal t :: *
- pgTypeName :: PGTypeID t -> PGName
- pgBinaryColumn :: PGTypeEnv -> PGTypeID t -> Bool
- class PGType t => PGParameter t a where
- pgEncode :: PGTypeID t -> a -> PGTextValue
- pgLiteral :: PGTypeID t -> a -> ByteString
- pgEncodeValue :: PGTypeEnv -> PGTypeID t -> a -> PGValue
- class PGType t => PGColumn t a where
- pgDecode :: PGTypeID t -> PGTextValue -> a
- pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> a
- pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> a
- 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 :: ByteString -> Builder
- pgDQuoteFrom :: [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.
PGNullValue | |
PGTextValue | The standard text encoding format (also used for unknown formats) |
| |
PGBinaryValue | Special binary-encoded data. Not supported in all cases. |
|
Instances
Show PGValue Source # | |
Eq PGValue Source # | |
PGQuery ByteString PGValues Source # | |
Defined in Database.PostgreSQL.Typed.Query pgRunQuery :: PGConnection -> ByteString -> IO (Int, [PGValues]) Source # unsafeModifyQuery :: ByteString -> (ByteString -> ByteString) -> ByteString Source # getQueryString :: PGTypeEnv -> ByteString -> ByteString Source # | |
PGType t => PGColumn t PGValue Source # | |
PGParameter "any" PGValue Source # | |
IsString (PGSimpleQuery PGValues) Source # | |
Defined in Database.PostgreSQL.Typed.Query fromString :: String -> PGSimpleQuery PGValues # |
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
.
Parameters that affect how marshalling happens. Currenly we force all other relevant parameters at connect time. Nothing values represent unknown.
PGTypeEnv | |
|
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.
PGName | |
|
Instances
Data PGName Source # | |
Defined in Database.PostgreSQL.Typed.Types 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 :: forall r r'. (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 # | |
IsString PGName Source # | Applies utf-8 encoding. |
Defined in Database.PostgreSQL.Typed.Types fromString :: String -> PGName # | |
Show PGName Source # | Unquoted |
Eq PGName Source # | |
Ord PGName Source # | |
PGRep PGName Source # | |
PGStringType t => PGColumn t PGName Source # | |
PGStringType t => PGParameter t PGName Source # | |
type PGRepType PGName Source # | |
Defined in Database.PostgreSQL.Typed.Dynamic |
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.
Nothing
The default, native Haskell representation of this type, which should be as close as possible to the PostgreSQL representation.
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
class PGType t => PGParameter t a where Source #
A PGParameter t a
instance describes how to encode a PostgreSQL type t
from a
.
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
.
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 # | |
Defined in Database.PostgreSQL.Typed.Types | |
PGStringType "character varying" Source # | |
Defined in Database.PostgreSQL.Typed.Types | |
PGStringType "name" Source # | |
Defined in Database.PostgreSQL.Typed.Types | |
PGStringType "text" Source # | |
Defined in Database.PostgreSQL.Typed.Types |
class PGType t => PGRecordType t Source #
Instances
PGRecordType "record" Source # | The generic anonymous record type, as created by |
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
.
buildPGValue :: Builder -> ByteString Source #
Shorthand for toStrict
. toLazyByteString