Safe Haskell | None |
---|---|
Language | Haskell2010 |
A DSL for declaration of query parameter encoders.
- data Params a
- unit :: Params ()
- param :: Value a -> Params a
- nullableParam :: Value a -> Params (Maybe a)
- data Value a
- bool :: Value Bool
- int2 :: Value Int16
- int4 :: Value Int32
- int8 :: Value Int64
- float4 :: Value Float
- float8 :: Value Double
- numeric :: Value Scientific
- char :: Value Char
- text :: Value Text
- bytea :: Value ByteString
- date :: Value Day
- timestamp :: Value LocalTime
- timestamptz :: Value UTCTime
- time :: Value TimeOfDay
- timetz :: Value (TimeOfDay, TimeZone)
- interval :: Value DiffTime
- uuid :: Value UUID
- inet :: Value (NetAddr IP)
- json :: Value Value
- jsonBytes :: Value ByteString
- jsonb :: Value Value
- jsonbBytes :: Value ByteString
- array :: Array a -> Value a
- enum :: (a -> Text) -> Value a
- unknown :: Value ByteString
- data Array a
- element :: Value a -> Array a
- nullableElement :: Value a -> Array (Maybe a)
- dimension :: (forall a. (a -> b -> a) -> a -> c -> a) -> Array b -> Array c
Params
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
(nullableParam
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
) (nullableParam
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
genderTexttext
where genderText gender = case gender of Male -> "male" Female -> "female"
Divisible Params Source # | |
Decidable Params Source # | |
Contravariant Params Source # | |
Semigroup (Params a) Source # | |
Monoid (Params a) Source # | |
Default (Params ()) Source # | Maps to |
(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 # | |
nullableParam :: Value a -> Params (Maybe a) Source #
Lift an individual nullable value encoder to a parameters encoder.
Value
An individual value encoder. Will be mapped to a single placeholder in the query.
Contravariant Value Source # | |
Default (Value Bool) Source # | Maps to |
Default (Value Char) Source # | Maps to |
Default (Value Double) Source # | Maps to |
Default (Value Float) Source # | Maps to |
Default (Value Int16) Source # | Maps to |
Default (Value Int32) Source # | Maps to |
Default (Value Int64) Source # | Maps to |
Default (Value (TimeOfDay, TimeZone)) Source # | Maps to |
Default (Value ByteString) Source # | Maps to |
Default (Value Scientific) Source # | Maps to |
Default (Value Text) Source # | Maps to |
Default (Value UTCTime) Source # | Maps to |
Default (Value Value) Source # | Maps to |
Default (Value UUID) Source # | Maps to |
Default (Value Day) Source # | Maps to |
Default (Value DiffTime) Source # | Maps to |
Default (Value TimeOfDay) Source # | Maps to |
Default (Value LocalTime) Source # | Maps to |
numeric :: Value Scientific Source #
Encoder of NUMERIC
values.
Encoder of CHAR
values.
Note that it supports UTF-8 values and
identifies itself under the TEXT
OID because of that.
bytea :: Value ByteString Source #
Encoder of BYTEA
values.
timestamptz :: Value UTCTime Source #
Encoder of TIMESTAMPTZ
values.
jsonBytes :: Value ByteString Source #
Encoder of JSON
values from raw JSON.
jsonbBytes :: Value ByteString Source #
Encoder of JSONB
values from raw JSON.
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 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
A generic array encoder.
Here's an example of its usage:
x :: Value [[Int64]] x = array (dimension foldl' (dimension foldl' (element 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 **field** = ANY($1) query instead.
dimension :: (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:
- An implementation of the left-fold operation,
such as
Data.Foldable.
, which determines the input value.foldl'
- A component encoder, which can be either another
dimension
,element
ornullableElement
.
Insert Many
It is not currently possible to pass in an array of encodable values
to use in an 'insert many' statement using Hasql. Instead, PostgreSQL's
(9.4 or later) unnest
function can be used to in an analogous way
to haskell's zip
function by passing in multiple arrays of values
to be zipped into the rows we want to insert:
insertMultipleLocations :: Statement (Vector (UUID, Double, Double)) () insertMultipleLocations = statement sql encoder decoder True where sql = "insert into location (id, x, y) select * from unnest ($1, $2, $3)" encoder = contramap Vector.unzip3 $ contrazip3 (vector Encoders.uuid) (vector Encoders.float8) (vector Encoders.float8) where vector value = Encoders.value (Encoders.array (Encoders.dimension foldl' (Encoders.element value))) decoder = Decoders.unit