hasql-1.4.0.1: An efficient PostgreSQL driver with 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 # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

noResult :: 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

rowMaybe :: Row a -> Result (Maybe a) Source #

Maybe one row or none.

rowVector :: Row a -> Result (Vector a) Source #

Zero or more rows packed into the vector.

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

rowList :: 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 = (,,) <$> (column . nullable) int8 <*> (column . nonNullable) text <*> (column . nonNullable) time
Instances
Monad Row Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

return :: a -> Row a #

fail :: String -> Row a #

Functor Row Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

Applicative Row Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

pure :: a -> Row a #

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

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

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

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

column :: NullableOrNot Value a -> Row a Source #

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

Nullability

data NullableOrNot decoder a Source #

Extensional specification of nullability over a generic decoder.

nonNullable :: decoder a -> NullableOrNot decoder a Source #

Specify that a decoder produces a non-nullable value.

nullable :: decoder a -> NullableOrNot decoder (Maybe a) Source #

Specify that a decoder produces a nullable value.

Value

data Value a Source #

Decoder of a value.

Instances
Functor Value Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

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 Unicode 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.

inet :: Value (NetAddr IP) Source #

Decoder of the INET 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 #

Lift an Array decoder to a Value decoder.

listArray :: NullableOrNot Value element -> Value [element] Source #

Lift a value decoder of element into a unidimensional array decoder producing a list.

This function is merely a shortcut to the following expression:

(array . dimension Control.Monad.replicateM . element)

Please notice that in case of multidimensional arrays nesting listArray decoder won't work. You have to explicitly construct the array decoder using array.

vectorArray :: Vector vector element => NullableOrNot Value element -> Value (vector element) Source #

Lift a value decoder of element into a unidimensional array decoder producing a generic vector.

This function is merely a shortcut to the following expression:

(array . dimension Data.Vector.Generic.replicateM . element)

Please notice that in case of multidimensional arrays nesting vectorArray decoder won't work. You have to explicitly construct the array decoder using array.

composite :: Composite a -> Value a Source #

Lift a Composite decoder to a 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 #

Lift 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 (dimension replicateM (dimension replicateM (element (nonNullable text))))
Instances
Functor Array Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

dimension :: (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:

  • An implementation of the replicateM function (Control.Monad.replicateM, Data.Vector.replicateM), which determines the output value.
  • A decoder of its components, which can be either another dimension or element.

element :: NullableOrNot Value a -> Array a Source #

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

Composite

data Composite a Source #

Composable decoder of composite values (rows, records).

Instances
Monad Composite Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

return :: a -> Composite a #

fail :: String -> Composite a #

Functor Composite Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

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

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

Applicative Composite Source # 
Instance details

Defined in Hasql.Private.Decoders

Methods

pure :: a -> Composite a #

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

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

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

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

field :: NullableOrNot Value a -> Composite a Source #

Lift a Value decoder into a Composite decoder for parsing of component values.