hasql-1.3: An 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 # 

Methods

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

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

Default (Result Int64) Source #

Maps to rowsAffected.

Methods

def :: Result Int64 #

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

Maps to (rowList def).

Methods

def :: Result [a] #

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

Maps to (rowMaybe def).

Methods

def :: Result (Maybe a) #

Default (Result ()) Source #

Maps to unit.

Methods

def :: Result () #

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

Maps to (fmap Identity (singleRow def).

Methods

def :: Result (Identity a) #

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

Maps to (rowVector def).

Methods

def :: Result (Vector a) #

unit :: Result () Source #

Decode no column 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 column decoders.

E.g.:

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

Instances

Monad Row Source # 

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 # 

Methods

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

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

Applicative Row Source # 

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 #

Default (Value a) => Default (Row (Maybe a)) Source # 

Methods

def :: Row (Maybe a) #

(Default (Value a1), Default (Value a2)) => Default (Row (a1, a2)) Source # 

Methods

def :: Row (a1, a2) #

Default (Value a) => Default (Row (Identity a)) Source # 

Methods

def :: Row (Identity a) #

column :: Value a -> Row a Source #

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

nullableColumn :: Value a -> Row (Maybe a) Source #

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

Value

data Value a Source #

Decoder of an individual column.

Instances

bool :: Value Bool Source #

Decoder of the BOOL columns.

int2 :: Value Int16 Source #

Decoder of the INT2 columns.

int4 :: Value Int32 Source #

Decoder of the INT4 columns.

int8 :: Value Int64 Source #

Decoder of the INT8 columns.

float4 :: Value Float Source #

Decoder of the FLOAT4 columns.

float8 :: Value Double Source #

Decoder of the FLOAT8 columns.

numeric :: Value Scientific Source #

Decoder of the NUMERIC columns.

char :: Value Char Source #

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

text :: Value Text Source #

Decoder of the TEXT columns.

bytea :: Value ByteString Source #

Decoder of the BYTEA columns.

date :: Value Day Source #

Decoder of the DATE columns.

timestamp :: Value LocalTime Source #

Decoder of the TIMESTAMP columns.

timestamptz :: Value UTCTime Source #

Decoder of the TIMESTAMPTZ columns.

NOTICE

Postgres does not store the timezone information of TIMESTAMPTZ. Instead it stores a UTC column 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 columns directly.

time :: Value TimeOfDay Source #

Decoder of the TIME columns.

timetz :: Value (TimeOfDay, TimeZone) Source #

Decoder of the TIMETZ columns.

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 column on the Haskell's side.

interval :: Value DiffTime Source #

Decoder of the INTERVAL columns.

uuid :: Value UUID Source #

Decoder of the UUID columns.

inet :: Value (NetAddr IP) Source #

Decoder of the INET columns.

json :: Value Value Source #

Decoder of the JSON columns into a JSON AST.

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

Decoder of the JSON columns into a raw JSON ByteString.

jsonb :: Value Value Source #

Decoder of the JSONB columns into a JSON AST.

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

Decoder of the JSONB columns 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 columns.

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

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

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

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

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

Lifts a custom column 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 column decoder:

x :: Value [[Text]]
x =
  array (dimension replicateM (dimension replicateM (element text)))

Instances

Functor Array Source # 

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:

element :: Value a -> Array a Source #

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

nullableElement :: Value a -> Array (Maybe a) Source #

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

Composite

data Composite a Source #

Composable decoder of composite columns (rows, records).

Instances

Monad Composite Source # 

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 # 

Methods

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

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

Applicative Composite Source # 

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 :: Value a -> Composite a Source #

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

nullableField :: Value a -> Composite (Maybe a) Source #

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