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

Copyright(c) 2011 MailRank Inc.
(c) 2011-2013 Leon P Smith
LicenseBSD3
MaintainerLeon P Smith <leon@melding-monads.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

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. 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 fromRational <$> field, although this idiom is additionally compatible with PostgreSQL's 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 ±Infinity 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.

Synopsis

Documentation

class FromField a where Source #

A type that may be converted from a SQL type.

Methods

fromField :: FieldParser a Source #

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 Source #

bool

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Char Source #

"char", bpchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Double Source #

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Float Source #

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int Source #

int2, int4, and if compiled as 64-bit code, int8 as well. This library was compiled as 64-bit code.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int16 Source #

int2

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int32 Source #

int2, int4

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int64 Source #

int2, int4, int8

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Integer Source #

int2, int4, int8

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField () Source #

void

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ByteString Source #

bytea, name, text, "char", bpchar, varchar, unknown

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ByteString Source #

bytea, name, text, "char", bpchar, varchar, unknown

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Scientific Source #

int2, int4, int8, float4, float8, numeric

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Text Source #

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UTCTime Source #

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Value Source #

json, jsonb

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Text Source #

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Oid Source #

oid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ZonedTime Source #

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField LocalTime Source #

timestamp

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField TimeOfDay Source #

time

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Day Source #

date

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UUID Source #

uuid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Date Source #

date

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ZonedTimestamp Source #

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UTCTimestamp Source #

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField LocalTimestamp Source #

timestamp

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Null Source #

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField HStoreMap Source # 
Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

FromField HStoreList Source #

hstore

Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

FromField [Char] Source #

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField a => FromField (Maybe a) Source #

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.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Ratio Integer) Source #

int2, int4, int8, float4, float8, numeric

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField a => FromField (IORef a) Source #

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.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField a => FromField (MVar a) Source #

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.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (CI Text) Source #

citext

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (CI Text) Source #

citext

Instance details

Defined in Database.PostgreSQL.Simple.FromField

(FromField a, Typeable a) => FromField (Vector a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.FromField

(FromField a, Typeable a) => FromField (IOVector a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.FromField

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

any postgresql array whose elements are compatible with type a

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Binary ByteString) Source #

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Binary ByteString) Source #

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

(FromField a, Typeable a) => FromField (PGRange a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Range

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

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

data Conversion a Source #

Instances
Monad Conversion Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Methods

(>>=) :: Conversion a -> (a -> Conversion b) -> Conversion b #

(>>) :: Conversion a -> Conversion b -> Conversion b #

return :: a -> Conversion a #

fail :: String -> Conversion a #

Functor Conversion Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Methods

fmap :: (a -> b) -> Conversion a -> Conversion b #

(<$) :: a -> Conversion b -> Conversion a #

Applicative Conversion Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Methods

pure :: a -> Conversion a #

(<*>) :: Conversion (a -> b) -> Conversion a -> Conversion b #

liftA2 :: (a -> b -> c) -> Conversion a -> Conversion b -> Conversion c #

(*>) :: Conversion a -> Conversion b -> Conversion b #

(<*) :: Conversion a -> Conversion b -> Conversion a #

Alternative Conversion Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

MonadPlus Conversion Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

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.

UnexpectedNull

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

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 a Source #

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 ByteString Source #

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.

name :: Field -> Maybe ByteString Source #

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 Oid Source #

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 -> Int Source #

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 -> Format Source #

This returns whether the data was returned in a binary or textual format. Analogous to libpq's PQfformat.

typeOid :: Field -> Oid Source #

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

newtype Oid #

Constructors

Oid CUInt 
Instances
Eq Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

(==) :: Oid -> Oid -> Bool #

(/=) :: Oid -> Oid -> Bool #

Ord Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

compare :: Oid -> Oid -> Ordering #

(<) :: Oid -> Oid -> Bool #

(<=) :: Oid -> Oid -> Bool #

(>) :: Oid -> Oid -> Bool #

(>=) :: Oid -> Oid -> Bool #

max :: Oid -> Oid -> Oid #

min :: Oid -> Oid -> Oid #

Read Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

Storable Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

sizeOf :: Oid -> Int #

alignment :: Oid -> Int #

peekElemOff :: Ptr Oid -> Int -> IO Oid #

pokeElemOff :: Ptr Oid -> Int -> Oid -> IO () #

peekByteOff :: Ptr b -> Int -> IO Oid #

pokeByteOff :: Ptr b -> Int -> Oid -> IO () #

peek :: Ptr Oid -> IO Oid #

poke :: Ptr Oid -> Oid -> IO () #

ToField Oid Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Oid -> Action Source #

FromField Oid Source #

oid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

data Format #

Constructors

Text 
Binary 
Instances
Enum Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Eq Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

optionalField :: FieldParser a -> FieldParser (Maybe a) Source #

For dealing with SQL null values outside of the FromField class. Alternatively, one could use optional, but that also turns type and conversion errors into Nothing, whereas this is more specific and turns only null values into Nothing.

fromJSONField :: (FromJSON a, Typeable a) => FieldParser a Source #

Parse a field to a JSON Value and convert that into a Haskell value using the FromJSON instance.

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 (Maybe Foo) will return Nothing on the json null value, and return an exception on SQL null value. Alternatively, one could write optionalField fromJSONField that will return Nothing on SQL null, and otherwise will call fromJSONField :: FieldParser Foo and then return Just the result value, or return its exception. If one would like to return 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