hasql-interpolate-0.1.0.2: QuasiQuoter that supports expression interpolation for hasql
Safe HaskellNone
LanguageHaskell2010

Hasql.Interpolate

Synopsis

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 |]

data Sql Source #

A SQL string with interpolated expressions.

Instances

Instances details
IsString Sql Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Sql

Methods

fromString :: String -> Sql #

Semigroup Sql Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Sql

Methods

(<>) :: Sql -> Sql -> Sql #

sconcat :: NonEmpty Sql -> Sql #

stimes :: Integral b => b -> Sql -> Sql #

Monoid Sql Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Sql

Methods

mempty :: Sql #

mappend :: Sql -> Sql -> Sql #

mconcat :: [Sql] -> Sql #

Interpolators

interp Source #

Arguments

:: DecodeResult b 
=> Bool

True if the Statement should be prepared

-> Sql 
-> Statement () b 

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

Expand
data ThreatLevel = None | Midnight

instance DecodeValue ThreatLevel where
  decodeValue = enum \case
    "none"     -> Just None
    "midnight" -> Just Midnight
    _          -> Nothing

Instances

Instances details
DecodeValue Bool Source #

Parse a postgres bool using bool

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Char Source #

Parse a postgres char using char

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Double Source #

Parse a postgres float8 using float8

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Float Source #

Parse a postgres float4 using float4

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Int16 Source #

Parse a postgres int2 using int2

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Int32 Source #

Parse a postgres int4 using int4

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Int64 Source #

Parse a postgres int8 using int8

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Scientific Source #

Parse a postgres numeric using numeric

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue UTCTime Source #

Parse a postgres timestamptz using timestamptz

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Text Source #

Parse a postgres text using text

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue UUID Source #

Parse a postgres uuid using uuid

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Day Source #

Parse a postgres date using date

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue DiffTime Source #

Parse a postgres interval using interval

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue LocalTime Source #

Parse a postgres timestamp using timestamp

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Json Source #

Parse a postgres json using json

Instance details

Defined in Hasql.Interpolate.Internal.Json

DecodeValue Jsonb Source #

Parse a postgres jsonb using jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

DecodeField a => DecodeValue [a] Source #

Parse a postgres array using listArray

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeValue :: Value [a] Source #

DecodeField a => DecodeValue (Vector a) Source #

Parse a postgres array using vectorArray

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

(Generic a, GToComposite (Rep a)) => DecodeValue (CompositeValue a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.CompositeValue

FromJSON a => DecodeValue (AsJsonb a) Source #

Parse a postgres jsonb to anything that is an instance of FromJSON

Instance details

Defined in Hasql.Interpolate.Internal.Json

FromJSON a => DecodeValue (AsJson a) Source #

Parse a postgres json to anything that is an instance of FromJSON

Instance details

Defined in Hasql.Interpolate.Internal.Json

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.

Instances

Instances details
DecodeValue a => DecodeField a Source #

Overlappable instance for parsing non-nullable values

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue a => DecodeField (Maybe a) Source #

Instance for parsing nullable values

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

class DecodeRow a where Source #

Determine a row decoder from a Haskell type. Derivable with generics for any product type.

Examples

Expand

A manual instance:

data T = T Int64 Bool Text

instance DecodeRow T where
  decodeRow = T
    $ column decodeField
    * column decodeField
    * column decodeField

A generic instance:

data T
 = T Int64 Bool Text
 deriving stock (Generic)
 deriving anyclass (DecodeRow)

Minimal complete definition

Nothing

Methods

decodeRow :: Row a Source #

default decodeRow :: (Generic a, GDecodeRow (Rep a)) => Row a Source #

Instances

Instances details
DecodeField a => DecodeRow (OneColumn a) Source #

Parse a single column row

Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

(DecodeField x1, DecodeField x2) => DecodeRow (x1, x2) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2) Source #

(DecodeField x1, DecodeField x2, DecodeField x3) => DecodeRow (x1, x2, x3) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4) => DecodeRow (x1, x2, x3, x4) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5) => DecodeRow (x1, x2, x3, x4, x5) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5, DecodeField x6) => DecodeRow (x1, x2, x3, x4, x5, x6) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5, x6) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5, DecodeField x6, DecodeField x7) => DecodeRow (x1, x2, x3, x4, x5, x6, x7) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5, x6, x7) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5, DecodeField x6, DecodeField x7, DecodeField x8) => DecodeRow (x1, x2, x3, x4, x5, x6, x7, x8) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5, x6, x7, x8) Source #

class DecodeResult a where Source #

Determine a result decoder from a Haskell type.

Instances

Instances details
DecodeResult () Source #

Ignore the query response (noResult)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeResult RowsAffected Source #

Parse the rows affected from the query result, as in an insert, update, or delete statement without a returning clause. (rowsAffected)

Instance details

Defined in Hasql.Interpolate.Internal.RowsAffected

DecodeRow a => DecodeResult [a] Source #

Parse any number of rows into a list (rowList)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeResult :: Result [a] Source #

DecodeRow a => DecodeResult (Maybe a) Source #

Parse zero or one rows, throw UnexpectedAmountOfRows otherwise. (rowMaybe)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeRow a => DecodeResult (Vector a) Source #

Parse any number of rows into a Vector (rowVector)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeRow a => DecodeResult (OneRow a) Source #

Parse a single row result, throw UnexpectedAmountOfRows otherwise. (singleRow)

Instance details

Defined in Hasql.Interpolate.Internal.OneRow

Encoders

class EncodeValue a where Source #

This type class determines which encoder we will apply to a field by its type.

Example

Expand
data ThreatLevel = None | Midnight

instance EncodeValue ThreatLevel where
  encodeValue = enum \case
    None     -> "none"
    Midnight -> "midnight"

Instances

Instances details
EncodeValue Bool Source #

Encode a Bool as a postgres boolean using bool

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Char Source #

Encode a Char as a postgres char using char

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Double Source #

Encode a Double as a postgres float8 using float8

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Float Source #

Encode a Float as a postgres float4 using float4

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Int16 Source #

Encode a Int16 as a postgres int2 using int2

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Int32 Source #

Encode a Int32 as a postgres int4 using int4

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Int64 Source #

Encode a Int64 as a postgres int8 using int8

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Scientific Source #

Encode a Scientific as a postgres numeric using numeric

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue UTCTime Source #

Encode a UTCTime as a postgres timestamptz using timestamptz

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Text Source #

Encode a Text as a postgres text using text

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue UUID Source #

Encode a UUID as a postgres uuid using uuid

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Day Source #

Encode a Day as a postgres date using date

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue DiffTime Source #

Encode a DiffTime as a postgres interval using interval

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue LocalTime Source #

Encode a LocalTime as a postgres timestamp using timestamp

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue Json Source #

Encode an Aeson Value to a postgres json using json

Instance details

Defined in Hasql.Interpolate.Internal.Json

EncodeValue Jsonb Source #

Encode an Aeson Value to a postgres jsonb using jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

EncodeField a => EncodeValue [a] Source #

Encode a list as a postgres array using foldableArray

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

Methods

encodeValue :: Value [a] Source #

EncodeField a => EncodeValue (Vector a) Source #

Encode a Vector as a postgres array using foldableArray

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

ToJSON a => EncodeValue (AsJsonb a) Source #

Encode anything that is an instance of ToJSON to a postgres jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

ToJSON a => EncodeValue (AsJson a) Source #

Encode anything that is an instance of ToJSON to a postgres json

Instance details

Defined in Hasql.Interpolate.Internal.Json

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.

Minimal complete definition

encodeField

Instances

Instances details
EncodeValue a => EncodeField a Source #

Overlappable instance for all non-nullable types.

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

EncodeValue a => EncodeField (Maybe a) Source #

Instance for all nullable types. Nothing is encoded as null.

Instance details

Defined in Hasql.Interpolate.Internal.Encoder

Newtypes for decoding/encoding

newtype OneRow a Source #

Constructors

OneRow 

Fields

Instances

Instances details
Eq a => Eq (OneRow a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneRow

Methods

(==) :: OneRow a -> OneRow a -> Bool #

(/=) :: OneRow a -> OneRow a -> Bool #

Show a => Show (OneRow a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneRow

Methods

showsPrec :: Int -> OneRow a -> ShowS #

show :: OneRow a -> String #

showList :: [OneRow a] -> ShowS #

Generic (OneRow a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneRow

Associated Types

type Rep (OneRow a) :: Type -> Type #

Methods

from :: OneRow a -> Rep (OneRow a) x #

to :: Rep (OneRow a) x -> OneRow a #

DecodeRow a => DecodeResult (OneRow a) Source #

Parse a single row result, throw UnexpectedAmountOfRows otherwise. (singleRow)

Instance details

Defined in Hasql.Interpolate.Internal.OneRow

type Rep (OneRow a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneRow

type Rep (OneRow a) = D1 ('MetaData "OneRow" "Hasql.Interpolate.Internal.OneRow" "hasql-interpolate-0.1.0.2-HU7UX9QPXoV4tg746sKi2p" 'True) (C1 ('MetaCons "OneRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOneRow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype OneColumn a Source #

Constructors

OneColumn 

Fields

Instances

Instances details
Eq a => Eq (OneColumn a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

Methods

(==) :: OneColumn a -> OneColumn a -> Bool #

(/=) :: OneColumn a -> OneColumn a -> Bool #

Show a => Show (OneColumn a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

Generic (OneColumn a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

Associated Types

type Rep (OneColumn a) :: Type -> Type #

Methods

from :: OneColumn a -> Rep (OneColumn a) x #

to :: Rep (OneColumn a) x -> OneColumn a #

DecodeField a => DecodeRow (OneColumn a) Source #

Parse a single column row

Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

type Rep (OneColumn a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

type Rep (OneColumn a) = D1 ('MetaData "OneColumn" "Hasql.Interpolate.Internal.OneColumn" "hasql-interpolate-0.1.0.2-HU7UX9QPXoV4tg746sKi2p" 'True) (C1 ('MetaCons "OneColumn" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOneColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype RowsAffected Source #

Constructors

RowsAffected 

Instances

Instances details
Eq RowsAffected Source # 
Instance details

Defined in Hasql.Interpolate.Internal.RowsAffected

Show RowsAffected Source # 
Instance details

Defined in Hasql.Interpolate.Internal.RowsAffected

Generic RowsAffected Source # 
Instance details

Defined in Hasql.Interpolate.Internal.RowsAffected

Associated Types

type Rep RowsAffected :: Type -> Type #

DecodeResult RowsAffected Source #

Parse the rows affected from the query result, as in an insert, update, or delete statement without a returning clause. (rowsAffected)

Instance details

Defined in Hasql.Interpolate.Internal.RowsAffected

type Rep RowsAffected Source # 
Instance details

Defined in Hasql.Interpolate.Internal.RowsAffected

type Rep RowsAffected = D1 ('MetaData "RowsAffected" "Hasql.Interpolate.Internal.RowsAffected" "hasql-interpolate-0.1.0.2-HU7UX9QPXoV4tg746sKi2p" 'True) (C1 ('MetaCons "RowsAffected" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRowsAffected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

newtype Json Source #

Newtype for DecodeValue / EncodeValue instances that converts between a postgres json type and an Aeson Value

Constructors

Json Value 

Instances

Instances details
DecodeValue Json Source #

Parse a postgres json using json

Instance details

Defined in Hasql.Interpolate.Internal.Json

EncodeValue Json Source #

Encode an Aeson Value to a postgres json using json

Instance details

Defined in Hasql.Interpolate.Internal.Json

newtype Jsonb Source #

Newtype for DecodeValue / EncodeValue instances that converts between a postgres json type and an Aeson Value

Constructors

Jsonb Value 

Instances

Instances details
DecodeValue Jsonb Source #

Parse a postgres jsonb using jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

EncodeValue Jsonb Source #

Encode an Aeson Value to a postgres jsonb using jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

newtype AsJson a Source #

Newtype for DecodeValue / EncodeValue instances that converts between a postgres json type and anything that is an instance of FromJSON / ToJSON

Constructors

AsJson a 

Instances

Instances details
FromJSON a => DecodeValue (AsJson a) Source #

Parse a postgres json to anything that is an instance of FromJSON

Instance details

Defined in Hasql.Interpolate.Internal.Json

ToJSON a => EncodeValue (AsJson a) Source #

Encode anything that is an instance of ToJSON to a postgres json

Instance details

Defined in Hasql.Interpolate.Internal.Json

newtype AsJsonb a Source #

Newtype for DecodeValue / EncodeValue instances that converts between a postgres jsonb type and anything that is an instance of FromJSON / ToJSON

Constructors

AsJsonb a 

Instances

Instances details
FromJSON a => DecodeValue (AsJsonb a) Source #

Parse a postgres jsonb to anything that is an instance of FromJSON

Instance details

Defined in Hasql.Interpolate.Internal.Json

ToJSON a => EncodeValue (AsJsonb a) Source #

Encode anything that is an instance of ToJSON to a postgres jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

newtype CompositeValue a Source #

Useful with DerivingVia to get a DecodeValue instance for any product type by parsing it as a composite.

Example

Expand
data Point = Point Int64 Int64
  deriving stock (Generic)
  deriving (DecodeValue) via CompositeValue Point

Constructors

CompositeValue a 

Instances

Instances details
(Generic a, GToComposite (Rep a)) => DecodeValue (CompositeValue a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.CompositeValue

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

Expand

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 #

Minimal complete definition

Nothing

Methods

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 (Params x) for x. An Int is also given to tally up how many sql fields are in the unzipped structure.

Example

Expand

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

Instances details
(EncodeValue x1, EncodeValue x2) => EncodeRow (x1, x2) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

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 # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

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 # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

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 # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

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 # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

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 # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

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 # 
Instance details

Defined in Hasql.Interpolate.Internal.EncodeRow

Methods

unzipWithEncoder :: (forall x. ((x1, x2, x3, x4, x5, x6, x7, x8) -> x -> x) -> x -> Params x -> Int -> r) -> r Source #