hasql-1.4.0.1: An efficient PostgreSQL driver with a flexible mapping API

Safe HaskellNone
LanguageHaskell2010

Hasql.Encoders

Contents

Description

A DSL for declaration of statement parameter encoders.

For compactness of names all the types defined here imply being an encoder. E.g., the Array type is an encoder of arrays, not the data-structure itself.

Synopsis

Parameters product

data Params a Source #

Encoder of some representation of a 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 =
  (fst >$< param (nonNullable int8)) <>
  (snd >$< param (nullable 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 (param (nonNullable int8)) (param (nullable 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 =
  (name >$< param (nonNullable text)) <>
  (gender >$< param (nonNullable genderValue)) <>
  (fromIntegral . age >$< param (nonNullable int8))

genderValue :: Value Gender
genderValue = enum genderText text where
  genderText gender = case gender of
    Male -> "male"
    Female -> "female"
Instances
Contravariant Params Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

contramap :: (a -> b) -> Params b -> Params a #

(>$) :: b -> Params b -> Params a #

Divisible Params Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

divide :: (a -> (b, c)) -> Params b -> Params c -> Params a #

conquer :: Params a #

Decidable Params Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

lose :: (a -> Void) -> Params a #

choose :: (a -> Either b c) -> Params b -> Params c -> Params a #

Semigroup (Params a) Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

(<>) :: Params a -> Params a -> Params a #

sconcat :: NonEmpty (Params a) -> Params a #

stimes :: Integral b => b -> Params a -> Params a #

Monoid (Params a) Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

mempty :: Params a #

mappend :: Params a -> Params a -> Params a #

mconcat :: [Params a] -> Params a #

noParams :: Params () Source #

No parameters. Same as mempty and conquered.

param :: NullableOrNot Value a -> Params a Source #

Lift a single parameter encoder, with its nullability specified, associating it with a single placeholder.

Nullability

data NullableOrNot encoder a Source #

Extensional specification of nullability over a generic encoder.

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

Specify that an encoder produces a non-nullable value.

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

Specify that an encoder produces a nullable value.

Value

data Value a Source #

Value encoder.

Instances
Contravariant Value Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

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

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

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

inet :: Value (NetAddr IP) Source #

Encoder of INET values.

json :: Value Value Source #

Encoder of JSON values from JSON AST.

jsonBytes :: Value ByteString Source #

Encoder of JSON values from raw JSON.

jsonb :: Value Value Source #

Encoder of JSONB values from JSON AST.

jsonbBytes :: Value ByteString Source #

Encoder of JSONB values from raw JSON.

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

Given a function, which maps a value into a textual enum label used on the DB side, produces an 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 value transimitted is any value encoded in the Postgres' Text data format. For reference, see the Formats and Format Codes section of the Postgres' documentation.

array :: Array a -> Value a Source #

Lift an array encoder into a parameter encoder.

foldableArray :: Foldable foldable => NullableOrNot Value element -> Value (foldable element) Source #

Lift a value encoder of element into a unidimensional array encoder of a foldable value.

This function is merely a shortcut to the following expression:

(array . dimension foldl' . element)

You can use it like this:

vectorOfInts :: Value (Vector Int64)
vectorOfInts = foldableArray (nonNullable int8)

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

Array

data Array a Source #

Generic array encoder.

Here's an example of its usage:

someParamsEncoder :: Params [[Int64]]
someParamsEncoder = param (nonNullable (array (dimension foldl' (dimension foldl' (element (nonNullable int8))))))

Please note that the PostgreSQL IN keyword does not accept an array, but rather a syntactical list of values, thus this encoder is not suited for that. Use a value = ANY($1) condition instead.

Instances
Contravariant Array Source # 
Instance details

Defined in Hasql.Private.Encoders

Methods

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

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

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

Lifts a Value encoder into an Array encoder.

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

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

Accepts:

  • An implementation of the left-fold operation, such as Data.Foldable.foldl', which determines the input value.
  • A component encoder, which can be either another dimension or element.