Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- sql :: QuasiQuoter
- data Sql
- interp :: DecodeResult b => Bool -> Sql -> Statement () b
- interpFoldl :: DecodeRow a => Bool -> (b -> a -> b) -> b -> Sql -> Statement () b
- interpWith :: Bool -> Result b -> Sql -> Statement () b
- class DecodeValue a where
- decodeValue :: Value a
- class DecodeField a where
- class DecodeRow a where
- class DecodeResult a where
- decodeResult :: Result a
- class EncodeValue a where
- encodeValue :: Value a
- class EncodeField a
- newtype OneRow a = OneRow {
- getOneRow :: a
- newtype OneColumn a = OneColumn {
- getOneColumn :: a
- newtype RowsAffected = RowsAffected {}
- newtype Json = Json Value
- newtype Jsonb = Jsonb Value
- newtype AsJson a = AsJson a
- newtype AsJsonb a = AsJsonb a
- newtype CompositeValue a = CompositeValue a
- toTable :: EncodeRow a => [a] -> Sql
- class EncodeRow a where
- unzipWithEncoder :: (forall x. (a -> x -> x) -> x -> Params x -> Int -> r) -> r
QuasiQuoters
sql :: QuasiQuoter Source #
QuasiQuoter that supports interpolation and splices. Produces a
Sql
.
#{..}
interpolates a haskell expression into a sql query.
example1 :: EncodeValue a => a -> Sql example1 x = [sql| select #{x} |]
^{..}
introduces a splice, which allows us to inject a sql
snippet along with the associated parameters into another sql
snippet.
example2 :: Sql example2 = [sql| ^{example1 True} where true |]
A SQL string with interpolated expressions.
Interpolators
Interpolate a Sql
into a Statement
using the DecodeResult
type class to determine the appropriate decoder.
example :: Int64 -> Statement () [(Int64, Int64)] example bonk = interp False [sql| select x, y from t where t.x > #{bonk} |]
interpFoldl :: DecodeRow a => Bool -> (b -> a -> b) -> b -> Sql -> Statement () b Source #
interpolate then consume with foldlRows
interpWith :: Bool -> Result b -> Sql -> Statement () b Source #
A more general version of interp
that allows for passing an
explicit decoder.
Decoders
class DecodeValue a where Source #
This type class determines which decoder we will apply to a query field by the type of the result.
Example
data ThreatLevel = None | Midnight instance DecodeValue ThreatLevel where decodeValue = enum \case "none" -> Just None "midnight" -> Just Midnight _ -> Nothing
decodeValue :: Value a Source #
Instances
class DecodeField a where Source #
You do not need to define instances for this class; The two
instances exported here cover all uses. The class only exists to
lift Value
to hasql's NullableOrNot
GADT.
decodeField :: NullableOrNot Value a Source #
Instances
DecodeValue a => DecodeField a Source # | Overlappable instance for parsing non-nullable values |
Defined in Hasql.Interpolate.Internal.Decoder decodeField :: NullableOrNot Value a Source # | |
DecodeValue a => DecodeField (Maybe a) Source # | Instance for parsing nullable values |
Defined in Hasql.Interpolate.Internal.Decoder decodeField :: NullableOrNot Value (Maybe a) Source # |
class DecodeRow a where Source #
Determine a row decoder from a Haskell type. Derivable with generics for any product type.
Examples
Nothing
Instances
class DecodeResult a where Source #
Determine a result decoder from a Haskell type.
decodeResult :: Result a Source #
Instances
Encoders
class EncodeValue a where Source #
This type class determines which encoder we will apply to a field by its type.
Example
data ThreatLevel = None | Midnight instance EncodeValue ThreatLevel where encodeValue = enum \case None -> "none" Midnight -> "midnight"
encodeValue :: Value a Source #
Instances
class EncodeField a Source #
You do not need to define instances for this class; The two
instances exported here cover all uses. The class only exists to
lift Value
to hasql's NullableOrNot
GADT.
encodeField
Instances
EncodeValue a => EncodeField a Source # | Overlappable instance for all non-nullable types. |
Defined in Hasql.Interpolate.Internal.Encoder | |
EncodeValue a => EncodeField (Maybe a) Source # | Instance for all nullable types. |
Defined in Hasql.Interpolate.Internal.Encoder encodeField :: NullableOrNot Value (Maybe a) |
Newtypes for decoding/encoding
Instances
Generic (OneRow a) Source # | |
Show a => Show (OneRow a) Source # | |
Eq a => Eq (OneRow a) Source # | |
DecodeRow a => DecodeResult (OneRow a) Source # | Parse a single row result, throw
|
Defined in Hasql.Interpolate.Internal.OneRow decodeResult :: Result (OneRow a) Source # | |
type Rep (OneRow a) Source # | |
Defined in Hasql.Interpolate.Internal.OneRow |
OneColumn | |
|
newtype RowsAffected Source #
Instances
Newtype for DecodeValue
/
EncodeValue
instances that converts
between a postgres json type and an Aeson Value
Instances
DecodeValue Json Source # | Parse a postgres |
Defined in Hasql.Interpolate.Internal.Json decodeValue :: Value Json Source # | |
EncodeValue Json Source # | |
Defined in Hasql.Interpolate.Internal.Json encodeValue :: Value Json Source # |
Newtype for DecodeValue
/
EncodeValue
instances that converts
between a postgres json type and an Aeson Value
Instances
DecodeValue Jsonb Source # | Parse a postgres |
Defined in Hasql.Interpolate.Internal.Json decodeValue :: Value Jsonb Source # | |
EncodeValue Jsonb Source # | |
Defined in Hasql.Interpolate.Internal.Json encodeValue :: Value Jsonb Source # |
Newtype for DecodeValue
/
EncodeValue
instances that converts
between a postgres json type and anything that is an instance of
FromJSON
/ ToJSON
AsJson a |
Instances
FromJSON a => DecodeValue (AsJson a) Source # | Parse a postgres |
Defined in Hasql.Interpolate.Internal.Json decodeValue :: Value (AsJson a) Source # | |
ToJSON a => EncodeValue (AsJson a) Source # | Encode anything that is an instance of |
Defined in Hasql.Interpolate.Internal.Json encodeValue :: Value (AsJson a) Source # |
Newtype for DecodeValue
/
EncodeValue
instances that converts
between a postgres jsonb type and anything that is an instance of
FromJSON
/ ToJSON
AsJsonb a |
Instances
FromJSON a => DecodeValue (AsJsonb a) Source # | Parse a postgres |
Defined in Hasql.Interpolate.Internal.Json decodeValue :: Value (AsJsonb a) Source # | |
ToJSON a => EncodeValue (AsJsonb a) Source # | Encode anything that is an instance of |
Defined in Hasql.Interpolate.Internal.Json encodeValue :: Value (AsJsonb a) Source # |
newtype CompositeValue a Source #
Useful with DerivingVia
to get a DecodeValue
instance for any
product type by parsing it as a composite.
Example
data Point = Point Int64 Int64 deriving stock (Generic) deriving (DecodeValue) via CompositeValue Point
Instances
(Generic a, GToComposite (Rep a)) => DecodeValue (CompositeValue a) Source # | |
Defined in Hasql.Interpolate.Internal.CompositeValue decodeValue :: Value (CompositeValue a) Source # |
toTable
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} |]
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
.
Instances
(EncodeField x1, EncodeField 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 # | |
(EncodeField x1, EncodeField x2, EncodeField 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 # | |
(EncodeField x1, EncodeField x2, EncodeField x3, EncodeField 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 # | |
(EncodeField x1, EncodeField x2, EncodeField x3, EncodeField x4, EncodeField 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 # | |
(EncodeField x1, EncodeField x2, EncodeField x3, EncodeField x4, EncodeField x5, EncodeField 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 # | |
(EncodeField x1, EncodeField x2, EncodeField x3, EncodeField x4, EncodeField x5, EncodeField x6, EncodeField 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 # | |
(EncodeField x1, EncodeField x2, EncodeField x3, EncodeField x4, EncodeField x5, EncodeField x6, EncodeField x7, EncodeField 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 # |