Stability | experimental |
---|---|
Maintainer | Leon P Smith <leon@melding-monads.com> |
Safe Haskell | None |
The FromField
typeclass, for converting a single value in a row
returned by a SQL query into a more useful Haskell representation.
Note that each instance of FromField
is documented by a list of
compatible postgresql types.
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.
Note that the Float
and Double
instances use attoparsec's double
conversion routine, which sacrifices some accuracy for speed. If you
need accuracy, consider first converting data to a Scientific
or Rational
type, and then converting to a floating-point type. If you are defining
your own FromRow
instances, this can be
achieved simply by
, although
this idiom is additionally compatible with PostgreSQL's fromRational
<$>
field
int8
and numeric
types. If this is unacceptable, you may find
fieldWith
useful.
Also note that while converting to a Double
through the Scientific
type
is likely somewhat faster than converting through the Rational
type,
the Scientific
type has no way to represent NaN
and ±Infinit
values.
Thus, if you need precision conversion of regular floating point values
and the possibility of receiving these special values from the backend,
stick with Rational
.
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.FromField ( FromField (fromField) , typeOid, returnError, ResultError (..) ) import Database.PostgreSQL.Simple.TypeInfo.Static (typoid, uuid) import qualified Data.ByteString.Char8 as B instance FromField UUID where fromField f mdata = if typeOid f /= typoid uuid then returnError Incompatible f "" else case B.unpack `fmap` mdata of Nothing -> returnError UnexpectedNull f "" Just dat -> case [ x | (x,t) <- reads dat, ("","") <- lex t ] of [x] -> return x _ -> returnError ConversionFailed f dat
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. One could hard-code the type oid, or
obtain it by other means, but in this case we simply pull it 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
- | Range {
- typoid :: !Oid
- typcategory :: !Char
- typdelim :: !Char
- typname :: !ByteString
- rngsubtype :: !TypeInfo
- | Composite {
- typoid :: !Oid
- typcategory :: !Char
- typdelim :: !Char
- typname :: !ByteString
- typrelid :: !Oid
- attributes :: !(Vector Attribute)
- = Basic {
- data Attribute = Attribute {
- attname :: !ByteString
- atttype :: !TypeInfo
- 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
- pgArrayFieldParser :: Typeable a => FieldParser a -> FieldParser (PGArray a)
- optionalField :: FieldParser a -> FieldParser (Maybe a)
- fromJSONField :: (FromJSON a, Typeable a) => FieldParser a
Documentation
A type that may be converted from a SQL type.
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
.
Note that retaining any reference to the Field
argument causes
the entire LibPQ.
to be retained. Thus, implementations
of Result
fromField
should return results that do not refer to this value
after the result have been evaluated to WHNF.
Note that as of postgresql-simple-0.4.0.0
, the ByteString
value
has already been copied out of the LibPQ.
before it has
been passed to Result
fromField
. This is because for short strings, it's
cheaper to copy the string than to set up a finalizer.
FromField Bool | bool |
FromField Char | "char" |
FromField Double | int2, int4, float4, float8 (Uses attoparsec's |
FromField Float | int2, float4 (Uses attoparsec's |
FromField Int | int2, int4, and if compiled as 64-bit code, int8 as well. This library was compiled as 64-bit code. |
FromField Int16 | int2 |
FromField Int32 | int2, int4 |
FromField Int64 | int2, int4, int8 |
FromField Integer | int2, int4, int8 |
FromField () | void |
FromField ByteString | bytea, name, text, "char", bpchar, varchar, unknown |
FromField ByteString | bytea, name, text, "char", bpchar, varchar, unknown |
FromField Scientific | int2, int4, int8, float4, float8, numeric |
FromField Text | name, text, "char", bpchar, varchar |
FromField UTCTime | timestamptz |
FromField Value | json |
FromField Text | name, text, "char", bpchar, varchar |
FromField Oid | oid |
FromField LocalTime | timestamp |
FromField ZonedTime | timestamptz |
FromField TimeOfDay | time |
FromField Day | date |
FromField UUID | uuid |
FromField Null | compatible with any data type, but the value must be null |
FromField Date | date |
FromField ZonedTimestamp | timestamptz |
FromField UTCTimestamp | timestamptz |
FromField LocalTimestamp | timestamp |
FromField HStoreMap | |
FromField HStoreList | hstore |
FromField [Char] | name, text, "char", bpchar, varchar |
FromField (Ratio Integer) | int2, int4, int8, float4, float8, numeric |
FromField a => FromField (Maybe a) | For dealing with null values. Compatible with any postgresql type
compatible with type |
FromField a => FromField (IORef a) | Compatible with the same set of types as |
FromField a => FromField (MVar a) | Compatible with the same set of types as |
FromField (CI Text) | citext |
FromField (CI Text) | citext |
(FromField a, Typeable a) => FromField (Vector a) | |
(FromField a, Typeable a) => FromField (IOVector a) | |
(FromField a, Typeable a) => FromField (PGArray a) | any postgresql array whose elements are compatible with type |
FromField (Binary ByteString) | bytea |
FromField (Binary ByteString) | bytea |
(FromField a, Typeable a) => FromField (PGRange a) | |
(FromField a, FromField b) => FromField (Either a b) | Compatible with both types. Conversions to type |
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.
Incompatible | The SQL and Haskell types are not compatible. |
| |
UnexpectedNull | A SQL |
| |
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). |
|
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
the 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.
A structure representing some of the metadata regarding a PostgreSQL
type, mostly taken from the pg_type
table.
Basic | |
| |
Array | |
| |
Range | |
| |
Composite | |
|
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
pgArrayFieldParser :: Typeable a => FieldParser a -> FieldParser (PGArray a)Source
optionalField :: FieldParser a -> FieldParser (Maybe a)Source
fromJSONField :: (FromJSON a, Typeable a) => FieldParser aSource
Parse a field to a JSON Value
and convert that into a
Haskell value using fromJSON
.
This can be used as the default implementation for the fromField
method for Haskell types that have a JSON representation in
PostgreSQL.
The Typeable
constraint is required to show more informative
error messages when parsing fails.
Note that fromJSONField :: FieldParser (
will return
Maybe
Foo)
on the json Nothing
null
value, and return an exception on SQL null
value. Alternatively, one could write
that will return optionalField
fromJSONFieldNothing
on SQL null
, and otherwise will call
fromJSONField :: FieldParser Foo
and then return
the
result value, or return its exception. If one would
like to return Just
Nothing
on both the SQL null
and json null
values,
one way to do it would be to write
\f mv ->
join
<$>
optionalField fromJSONField f mv