hasql-0.19.8: A very efficient PostgreSQL driver and a flexible mapping API

Safe HaskellNone
LanguageHaskell2010

Hasql.Decoders

Contents

Description

A DSL for declaration of result decoders.

Synopsis

Result

data Result a Source

Decoder of a query result.

Instances

Functor Result Source 
Default (Result Int64) Source

Maps to rowsAffected.

Default (Row a) => Default (Result [a]) Source

Maps to (rowsList def).

Default (Result ()) Source

Maps to unit.

Default (Row a) => Default (Result (Maybe a)) Source

Maps to (maybeRow def).

Default (Row a) => Default (Result (Identity a)) Source

Maps to (fmap Identity (singleRow def).

Default (Row a) => Default (Result (Vector a)) Source

Maps to (rowsVector def).

unit :: Result () Source

Decode no value from the result.

Useful for statements like INSERT or CREATE.

rowsAffected :: Result Int64 Source

Get the amount of rows affected by such statements as UPDATE or DELETE.

singleRow :: Row a -> Result a Source

Exactly one row. Will raise the UnexpectedAmountOfRows error if it's any other.

Specialized multi-row results

maybeRow :: Row a -> Result (Maybe a) Source

Maybe one row or none.

rowsVector :: Row a -> Result (Vector a) Source

Zero or more rows packed into the vector.

It's recommended to prefer this function to rowsList, since it performs notably better.

rowsList :: Row a -> Result [a] Source

Zero or more rows packed into the list.

Multi-row traversers

foldlRows :: (a -> b -> a) -> a -> Row b -> Result a Source

Foldl multiple rows.

foldrRows :: (b -> a -> a) -> a -> Row b -> Result a Source

Foldr multiple rows.

Row

data Row a Source

Decoder of an individual row, which gets composed of column value decoders.

E.g.:

x :: Row (Maybe Int64, Text, TimeOfDay)
x =
  (,,) <$> nullableValue int8 <*> value text <*> value time

value :: Value a -> Row a Source

Lift an individual non-nullable value decoder to a composable row decoder.

nullableValue :: Value a -> Row (Maybe a) Source

Lift an individual nullable value decoder to a composable row decoder.

Value

bool :: Value Bool Source

Decoder of the BOOL values.

int2 :: Value Int16 Source

Decoder of the INT2 values.

int4 :: Value Int32 Source

Decoder of the INT4 values.

int8 :: Value Int64 Source

Decoder of the INT8 values.

float4 :: Value Float Source

Decoder of the FLOAT4 values.

float8 :: Value Double Source

Decoder of the FLOAT8 values.

numeric :: Value Scientific Source

Decoder of the NUMERIC values.

char :: Value Char Source

Decoder of the CHAR values. Note that it supports UTF-8 values.

text :: Value Text Source

Decoder of the TEXT values.

bytea :: Value ByteString Source

Decoder of the BYTEA values.

date :: Value Day Source

Decoder of the DATE values.

timestamp :: Value LocalTime Source

Decoder of the TIMESTAMP values.

timestamptz :: Value UTCTime Source

Decoder of the TIMESTAMPTZ values.

NOTICE

Postgres does not store the timezone information of TIMESTAMPTZ. Instead it stores a UTC value and performs silent conversions to the currently set timezone, when dealt with in the text format. However this library bypasses the silent conversions and communicates with Postgres using the UTC values directly.

time :: Value TimeOfDay Source

Decoder of the TIME values.

timetz :: Value (TimeOfDay, TimeZone) Source

Decoder of the TIMETZ values.

Unlike in case of TIMESTAMPTZ, Postgres does store the timezone information for TIMETZ. However the Haskell's "time" library does not contain any composite type, that fits the task, so we use a pair of TimeOfDay and TimeZone to represent a value on the Haskell's side.

interval :: Value DiffTime Source

Decoder of the INTERVAL values.

uuid :: Value UUID Source

Decoder of the UUID values.

json :: Value Value Source

Decoder of the JSON values into a JSON AST.

jsonBytes :: (ByteString -> Either Text a) -> Value a Source

Decoder of the JSON values into a raw JSON ByteString.

jsonb :: Value Value Source

Decoder of the JSONB values into a JSON AST.

jsonbBytes :: (ByteString -> Either Text a) -> Value a Source

Decoder of the JSONB values into a raw JSON ByteString.

array :: Array a -> Value a Source

Lifts the Array decoder to the Value decoder.

composite :: Composite a -> Value a Source

Lifts the Composite decoder to the Value decoder.

hstore :: (forall m. Monad m => Int -> m (Text, Maybe Text) -> m a) -> Value a Source

A generic decoder of HSTORE values.

Here's how you can use it to construct a specific value:

x :: Value [(Text, Maybe Text)]
x =
  hstore replicateM

enum :: (Text -> Maybe a) -> Value a Source

Given a partial mapping from text to value, produces a decoder of that value.

custom :: (Bool -> ByteString -> Either Text a) -> Value a Source

Lifts a custom value decoder function to a Value decoder.

Array

data Array a Source

A generic array decoder.

Here's how you can use it to produce a specific array value decoder:

x :: Value [[Text]]
x =
  array (arrayDimension replicateM (arrayDimension replicateM (arrayValue text)))

Instances

arrayDimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b Source

A function for parsing a dimension of an array. Provides support for multi-dimensional arrays.

Accepts:

arrayValue :: Value a -> Array a Source

Lift a Value decoder into an Array decoder for parsing of non-nullable leaf values.

arrayNullableValue :: Value a -> Array (Maybe a) Source

Lift a Value decoder into an Array decoder for parsing of nullable leaf values.

Composite

data Composite a Source

Composable decoder of composite values (rows, records).

compositeValue :: Value a -> Composite a Source

Lift a Value decoder into a Composite decoder for parsing of non-nullable leaf values.

compositeNullableValue :: Value a -> Composite (Maybe a) Source

Lift a Value decoder into a Composite decoder for parsing of nullable leaf values.