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

Safe HaskellNone
LanguageHaskell2010

Hasql.Encoders

Contents

Description

A DSL for declaration of query parameter encoders.

Synopsis

Params

data Params a Source

Encoder of some representation of the parameters product.

Has instances of Contravariant, Divisible and Monoid, which you can use to compose multiple parameters together. E.g.,

someParamsEncoder :: Params (Int64, Maybe Text)
someParamsEncoder =
  contramap fst (value int8) <>
  contramap snd (nullableValue text)

As a general solution for tuples of any arity, instead of fst and snd, consider the functions of the contrazip family from the "contravariant-extras" package. E.g., here's how you can achieve the same as the above:

someParamsEncoder :: Params (Int64, Maybe Text)
someParamsEncoder =
  contrazip2 (value int8) (nullableValue text)

Here's how you can implement encoders for custom composite types:

data Person =
  Person { name :: Text, gender :: Gender, age :: Int }

data Gender =
  Male | Female

personParams :: Params Person
personParams =
  contramap name (value text) <>
  contramap gender (value genderValue) <>
  contramap (fromIntegral . age) (value int8)

genderValue :: Value Gender
genderValue =
  contramap genderText text
  where
    genderText gender =
      case gender of
        Male -> "male"
        Female -> "female"

Instances

Divisible Params Source 
Contravariant Params Source 
Monoid (Params a) Source 
Default (Params ()) Source

Maps to unit.

(Default (Value a1), Default (Value a2)) => Default (Params (a1, a2)) Source 
(Default (Value a1), Default (Value a2), Default (Value a3)) => Default (Params (a1, a2, a3)) Source 
(Default (Value a1), Default (Value a2), Default (Value a3), Default (Value a4)) => Default (Params (a1, a2, a3, a4)) Source 
(Default (Value a1), Default (Value a2), Default (Value a3), Default (Value a4), Default (Value a5)) => Default (Params (a1, a2, a3, a4, a5)) Source 
Default (Value a) => Default (Params (Identity a)) Source 

unit :: Params () Source

Encode no parameters.

value :: Value a -> Params a Source

Lift an individual value encoder to a parameters encoder.

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

Lift an individual nullable value encoder to a parameters encoder.

Value

bool :: Value Bool Source

Encoder of BOOL values.

int2 :: Value Int16 Source

Encoder of INT2 values.

int4 :: Value Int32 Source

Encoder of INT4 values.

int8 :: Value Int64 Source

Encoder of INT8 values.

float4 :: Value Float Source

Encoder of FLOAT4 values.

float8 :: Value Double Source

Encoder of FLOAT8 values.

numeric :: Value Scientific Source

Encoder of NUMERIC values.

char :: Value Char Source

Encoder of CHAR values. Note that it supports UTF-8 values and identifies itself under the TEXT OID because of that.

text :: Value Text Source

Encoder of TEXT values.

bytea :: Value ByteString Source

Encoder of BYTEA values.

date :: Value Day Source

Encoder of DATE values.

timestamp :: Value LocalTime Source

Encoder of TIMESTAMP values.

timestamptz :: Value UTCTime Source

Encoder of TIMESTAMPTZ values.

time :: Value TimeOfDay Source

Encoder of TIME values.

timetz :: Value (TimeOfDay, TimeZone) Source

Encoder of TIMETZ values.

interval :: Value DiffTime Source

Encoder of INTERVAL values.

uuid :: Value UUID Source

Encoder of UUID values.

json :: Value Value Source

Encoder of JSON values.

jsonb :: Value Value Source

Encoder of JSONB values.

array :: Array a -> Value a Source

Unlifts the Array encoder to the plain Value encoder.

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

Given a function, which maps the value into the textual enum label from the DB side, produces a encoder of that value.

unknown :: Value ByteString Source

Identifies the value with the PostgreSQL's "unknown" type, thus leaving it up to Postgres to infer the actual type of the value.

The bytestring needs to be encoded according to the Postgres' binary format of the type it expects.

Essentially this is a low-level hook for encoding of values with custom codecs. The "postgresql-binary" library will provide you with the toolchain.

Array

data Array a Source

A generic array encoder.

Here's an example of its usage:

x :: Value [[Int64]]
x =
  array (arrayDimension foldl' (arrayDimension foldl' (arrayValue int8)))

arrayValue :: Value a -> Array a Source

Lifts the Value encoder into the Array encoder of a non-nullable value.

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

Lifts the Value encoder into the Array encoder of a nullable value.

arrayDimension :: (forall a. (a -> b -> a) -> a -> c -> a) -> Array b -> Array c Source

An encoder of an array dimension, which thus provides support for multidimensional arrays.

Accepts: