postgresql-simple-0.4.7.0: Mid-Level PostgreSQL client library

Safe HaskellNone

Database.PostgreSQL.Simple.FromField

Synopsis

Documentation

class FromField a whereSource

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.

Note that retaining any reference to the Field argument causes the entire LibPQ.Result to be retained. Thus, implementations of 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.Result before it has been passed to fromField. This is because for short strings, it's cheaper to copy the string than to set up a finalizer.

Instances

FromField Bool

bool

FromField Char

"char"

FromField Double

int2, int4, float4, float8 (Uses attoparsec's double routine, for better accuracy convert to Scientific or Rational first)

FromField Float

int2, float4 (Uses attoparsec's double routine, for better accuracy convert to Scientific or Rational first)

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, 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 UUID

uuid

FromField TimeOfDay

time

FromField ZonedTime

timestamptz

FromField LocalTime

timestamp

FromField Day

date

FromField Date

date

FromField ZonedTimestamp

timestamptz

FromField UTCTimestamp

timestamptz

FromField LocalTimestamp

timestamp

FromField Null

compatible with any data type, but the value must be null

FromField HStoreMap 
FromField HStoreList

hstore

FromField [Char]

name, text, "char", bpchar, varchar

FromField (Ratio Integer)

int2, int4, float4, float8, numeric

FromField a => FromField (Maybe a)

For dealing with null values. Compatible with any postgresql type compatible with type a. Note that the type is not checked if the value is null, although it is inadvisable to rely on this behavior.

(FromField a, Typeable a) => FromField (Vector a) 
(FromField a, Typeable a) => FromField (IOVector a) 
FromField a => FromField (MVar a)

Compatible with the same set of types as a. Note that modifying the MVar does not have any effects outside the local process on the local machine.

FromField a => FromField (IORef a)

Compatible with the same set of types as a. Note that modifying the IORef does not have any effects outside the local process on the local machine.

(FromField a, Typeable a) => FromField (PGArray a)

any postgresql array whose elements are compatible with type a

FromField (Binary ByteString)

bytea

FromField (Binary ByteString)

bytea

(FromField a, FromField b) => FromField (Either a b)

Compatible with both types. Conversions to type b are preferred, the conversion to type a will be tried after the Right conversion fails.

type FieldParser a = Field -> Maybe ByteString -> Conversion aSource

data Conversion a Source

Instances

Monad Conversion 
Functor Conversion 
MonadPlus Conversion 
Applicative Conversion 
Alternative Conversion 

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

errSQLType :: String
 
errSQLTableOid :: Maybe Oid
 
errSQLField :: String
 
errHaskellType :: String
 
errMessage :: String
 
UnexpectedNull

A SQL NULL was encountered when the Haskell type did not permit it.

Fields

errSQLType :: String
 
errSQLTableOid :: Maybe Oid
 
errSQLField :: String
 
errHaskellType :: String
 
errMessage :: String
 
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

errSQLType :: String
 
errSQLTableOid :: Maybe Oid
 
errSQLField :: String
 
errHaskellType :: String
 
errMessage :: String
 

Instances

Eq ResultError 
Show ResultError 
Typeable ResultError 
Exception ResultError 

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.

data Field Source

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.

data TypeInfo Source

A structure representing some of the metadata regarding a PostgreSQL type, mostly taken from the pg_type table.

Constructors

Basic 

Fields

typoid :: !Oid
 
typcategory :: !Char
 
typdelim :: !Char
 
typname :: !ByteString
 
Array 

Fields

typoid :: !Oid
 
typcategory :: !Char
 
typdelim :: !Char
 
typname :: !ByteString
 
typelem :: !TypeInfo
 
Range 

Fields

typoid :: !Oid
 
typcategory :: !Char
 
typdelim :: !Char
 
typname :: !ByteString
 
rngsubtype :: !TypeInfo
 
Composite 

Fields

typoid :: !Oid
 
typcategory :: !Char
 
typdelim :: !Char
 
typname :: !ByteString
 
typrelid :: !Oid
 
attributes :: !(Vector Attribute)
 

Instances

Show TypeInfo 

data Attribute Source

Constructors

Attribute 

Fields

attname :: !ByteString
 
atttype :: !TypeInfo
 

Instances

Show Attribute 

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.

typeOid :: Field -> OidSource

This returns the type oid associated with the column. Analogous to libpq's PQftype.

newtype Oid

Constructors

Oid CUInt 

Instances

Eq Oid 
Ord Oid 
Read Oid 
Show Oid 
Storable Oid 
ToField Oid 
FromField Oid

oid

data Format

Constructors

Text 
Binary 

Instances

Enum Format 
Eq Format 
Ord Format 
Show Format 

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.