Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class EncodeRow a where
- unzipWithEncoder :: (forall x. (a -> x -> x) -> x -> Params x -> Int -> r) -> r
- class GEncodeRow a where
- gUnzipWithEncoder :: (forall x. (a p -> x -> x) -> x -> Params x -> Int -> r) -> r
- toTable :: EncodeRow a => [a] -> Sql
Documentation
class EncodeRow a where Source #
Nothing
unzipWithEncoder :: (forall x. (a -> x -> x) -> x -> Params x -> Int -> r) -> r Source #
The continuation (forall x. (a -> x -> x) -> x -> E.Params x
-> Int -> r)
is given cons (a -> x -> x)
and nil (x)
for some
existential type x
and an encoder (
) for Params
xx
. An
Int is also given to tally up how many sql fields are in the
unzipped structure.
Example
Consider the following manually written instance:
data Blerg = Blerg Int64 Bool Text Char instance EncodeRow Blerg where unzipWithEncoder k = k cons nil enc 4 where cons (Blerg a b c d) ~(as, bs, cs, ds) = (a : as, b : bs, c : cs, d : ds) nil = ([], [], [], []) enc = (((x, _, _, _) -> x) >$< param encodeField) <> (((_, x, _, _) -> x) >$< param encodeField) <> (((_, _, x, _) -> x) >$< param encodeField) <> (((_, _, _, x) -> x) >$< param encodeField)
We chose ([Int64], [Bool], [Text], [Char])
as our existential
type. If we instead use the default instance based on
GEncodeRow
then we would produce the same code as the
instance below:
instance EncodeRow Blerg where unzipWithEncoder k = k cons nil enc 4 where cons (Blerg a b c d) ~(~(as, bs), ~(cs, ds)) = ((a : as, b : bs), (c : cs, d : ds)) nil = (([], []), ([], [])) enc = ((((x, _), _) -> x) >$< param encodeField) <> ((((_, x), _) -> x) >$< param encodeField) <> (((_ , (x, _)) -> x) >$< param encodeField) <> (((_ , (_, x)) -> x) >$< param encodeField)
The notable difference being we don't produce a flat tuple, but
instead produce a balanced tree of tuples isomorphic to the
balanced tree of
from the generic :*:
Rep
of Blerg
.
default unzipWithEncoder :: (Generic a, GEncodeRow (Rep a)) => (forall x. (a -> x -> x) -> x -> Params x -> Int -> r) -> r Source #
Instances
(EncodeValue x1, EncodeValue x2) => EncodeRow (x1, x2) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # | |
(EncodeValue x1, EncodeValue x2, EncodeValue x3) => EncodeRow (x1, x2, x3) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2, x3) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # | |
(EncodeValue x1, EncodeValue x2, EncodeValue x3, EncodeValue x4) => EncodeRow (x1, x2, x3, x4) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2, x3, x4) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # | |
(EncodeValue x1, EncodeValue x2, EncodeValue x3, EncodeValue x4, EncodeValue x5) => EncodeRow (x1, x2, x3, x4, x5) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2, x3, x4, x5) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # | |
(EncodeValue x1, EncodeValue x2, EncodeValue x3, EncodeValue x4, EncodeValue x5, EncodeValue x6) => EncodeRow (x1, x2, x3, x4, x5, x6) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2, x3, x4, x5, x6) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # | |
(EncodeValue x1, EncodeValue x2, EncodeValue x3, EncodeValue x4, EncodeValue x5, EncodeValue x6, EncodeValue x7) => EncodeRow (x1, x2, x3, x4, x5, x6, x7) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2, x3, x4, x5, x6, x7) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # | |
(EncodeValue x1, EncodeValue x2, EncodeValue x3, EncodeValue x4, EncodeValue x5, EncodeValue x6, EncodeValue x7, EncodeValue x8) => EncodeRow (x1, x2, x3, x4, x5, x6, x7, x8) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow unzipWithEncoder :: (forall x. ((x1, x2, x3, x4, x5, x6, x7, x8) -> x -> x) -> x -> Params x -> Int -> r) -> r Source # |
class GEncodeRow a where Source #
gUnzipWithEncoder :: (forall x. (a p -> x -> x) -> x -> Params x -> Int -> r) -> r Source #
Instances
EncodeField a => GEncodeRow (K1 i a :: Type -> Type) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow | |
(GEncodeRow a, GEncodeRow b) => GEncodeRow (a :*: b) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow | |
GEncodeRow x => GEncodeRow (M1 t i x) Source # | |
Defined in Hasql.Interpolate.Internal.EncodeRow |
toTable :: EncodeRow a => [a] -> Sql Source #
toTable
takes some list of products into the corresponding
relation in sql. It is applying the unnest
based technique
described in the hasql
documentation.
Example
Here is a small example that takes a haskell list and inserts it
into a table blerg
which has columns x
, y
, and z
of type
int8
, boolean
, and text
respectively.
toTableExample :: [(Int64, Bool, Text)] -> Statement () () toTableExample rowsToInsert = interp [sql| insert into blerg (x, y, z) select * from ^{toTable rowsToInsert} |]
This is driven by the EncodeRow
type class that has a
default implementation for product types that are an instance of
Generic
. So the following also works:
data Blerg = Blerg Int64 Bool Text deriving stock (Generic) deriving anyclass (EncodeRow) toTableExample :: [Blerg] -> Statement () () toTableExample blergs = interp [sql| insert into blerg (x, y, z) select * from ^{toTable blergs} |]