Portability | portable |
---|---|
Stability | experimental |
Maintainer | Leon P Smith <leon@melding-monads.com> |
Safe Haskell | None |
Database.PostgreSQL.Simple.FromField
Description
The FromField
typeclass, for converting a single value in a row
returned by a SQL query into a more useful Haskell representation.
A Haskell numeric type is considered to be compatible with all
PostgreSQL numeric types that are less accurate than it. For instance,
the Haskell Double
type is compatible with the PostgreSQL's 32-bit
int
type because it can represent a int
exactly. On the other hand,
since a Double
might lose precision if representing PostgreSQL's 64-bit
bigint
, the two are not considered compatible.
Because FromField
is a typeclass, one may provide conversions to
additional Haskell types without modifying postgresql-simple. This is
particularly useful for supporting PostgreSQL types that postgresql-simple
does not support out-of-box. Here's an example of what such an instance
might look like for a UUID type that implements the Read
class:
import Data.UUID ( UUID ) import Database.PostgreSQL.Simple.BuiltinTypes ( BuiltinType(UUID), builtin2oid ) import qualified Data.ByteString as B instance FromField UUID where fromField f mdata = if typeOid f /= builtin2oid UUID then returnError Incompatible f "" else case B.unpack `fmap` mdata of Nothing -> returnError UnexpectedNull f "" Just data -> case [ x | (x,t) <- reads data, ("","") <- lex t ] of [x] -> Ok x _ -> returnError ConversionError f data
Note that because PostgreSQL's uuid
type is built into postgres and is
not provided by an extension, the typeOid
of uuid
does not change and
thus we can examine it directly. Here, we simply pull the type oid out
of the static table provided by postgresql-simple.
On the other hand if the type is provided by an extension, such as
PostGIS
or hstore
, then the typeOid
is not stable and can vary from
database to database. In this case it is recommended that FromField
instances use typename
instead.
- class FromField a where
- fromField :: FieldParser a
- type FieldParser a = Field -> Maybe ByteString -> Conversion a
- data Conversion a
- runConversion :: Conversion a -> Connection -> IO (Ok a)
- conversionMap :: (Ok a -> Ok b) -> Conversion a -> Conversion b
- conversionError :: Exception err => err -> Conversion a
- data ResultError
- = Incompatible { }
- | UnexpectedNull { }
- | ConversionFailed { }
- returnError :: forall a err. (Typeable a, Exception err) => (String -> Maybe Oid -> String -> String -> String -> err) -> Field -> String -> Conversion a
- data Field
- typename :: Field -> Conversion ByteString
- data TypeInfo
- = Basic {
- typoid :: !Oid
- typcategory :: !Char
- typdelim :: !Char
- typname :: !ByteString
- | Array {
- typoid :: !Oid
- typcategory :: !Char
- typdelim :: !Char
- typname :: !ByteString
- typelem :: !TypeInfo
- = Basic {
- typeInfo :: Field -> Conversion TypeInfo
- typeInfoByOid :: Oid -> Conversion TypeInfo
- name :: Field -> Maybe ByteString
- tableOid :: Field -> Maybe Oid
- tableColumn :: Field -> Int
- format :: Field -> Format
- typeOid :: Field -> Oid
- newtype Oid = Oid CUInt
- data Format
Documentation
A type that may be converted from a SQL type.
Methods
fromField :: FieldParser aSource
Convert a SQL value to a Haskell value.
Returns a list of exceptions if the conversion fails. In the case of
library instances, this will usually be a single ResultError
, but
may be a UnicodeException
.
Implementations of fromField
should not retain any references to
the Field
nor the ByteString
arguments after the result has
been evaluated to WHNF. Such a reference causes the entire
LibPQ.
to be retained.
Result
For example, the instance for ByteString
uses copy
to avoid
such a reference, and that using bytestring functions such as drop
and takeWhile
alone will also trigger this memory leak.
Instances
type FieldParser a = Field -> Maybe ByteString -> Conversion aSource
data Conversion a Source
runConversion :: Conversion a -> Connection -> IO (Ok a)Source
conversionMap :: (Ok a -> Ok b) -> Conversion a -> Conversion bSource
conversionError :: Exception err => err -> Conversion aSource
data ResultError Source
Exception thrown if conversion from a SQL value to a Haskell value fails.
Constructors
Incompatible | The SQL and Haskell types are not compatible. |
Fields
| |
UnexpectedNull | A SQL |
Fields
| |
ConversionFailed | The SQL value could not be parsed, or could not be represented as a valid Haskell value, or an unexpected low-level error occurred (e.g. mismatch between metadata and actual data in a row). |
Fields
|
returnError :: forall a err. (Typeable a, Exception err) => (String -> Maybe Oid -> String -> String -> String -> err) -> Field -> String -> Conversion aSource
Given one of the constructors from ResultError
, the field,
and an errMessage
, this fills in the other fields in the
exception value and returns it in a 'Left . SomeException'
constructor.
A Field represents metadata about a particular field
You don't particularly want to retain these structures for a long period of time, as they will retain the entire query result, not just the field metadata
typename :: Field -> Conversion ByteStringSource
Returns the data type name. This is the preferred way of identifying types that do not have a stable type oid, such as types provided by extensions to PostgreSQL.
More concretely, it returns the typname
column associated with the
type oid in the pg_type
table. First, postgresql-simple will check
built-in, static table. If the type oid is not there, postgresql-simple
will check a per-connection cache, and then finally query the database's
meta-schema.
Constructors
Basic | |
Fields
| |
Array | |
Fields
|
name :: Field -> Maybe ByteStringSource
Returns the name of the column. This is often determined by a table
definition, but it can be set using an as
clause.
tableOid :: Field -> Maybe OidSource
Returns the name of the object id of the table
associated with the
column, if any. Returns Nothing
when there is no such table;
for example a computed column does not have a table associated with it.
Analogous to libpq's PQftable
.
tableColumn :: Field -> IntSource
If the column has a table associated with it, this returns the number
off the associated table column. Numbering starts from 0. Analogous
to libpq's PQftablecol
.
format :: Field -> FormatSource
This returns whether the data was returned in a binary or textual format.
Analogous to libpq's PQfformat
.
This returns the type oid associated with the column. Analogous
to libpq's PQftype
.
newtype Oid