hasql-1.2: An efficient PostgreSQL driver and a flexible mapping API

Safe HaskellNone
LanguageHaskell2010

Hasql.Query

Synopsis

Documentation

data Query a b Source #

A specification of a strictly single-statement query, which can be parameterized and prepared.

Consists of the following:

  • SQL template,
  • params encoder,
  • result decoder,
  • a flag, determining whether it should be prepared.

The SQL template must be formatted according to Postgres' standard, with any non-ASCII characters of the template encoded using UTF-8. According to the format, parameters must be referred to using the positional notation, as in the following: $1, $2, $3 and etc. Those references must be used to refer to the values of the Params encoder.

Following is an example of the declaration of a prepared statement with its associated codecs.

selectSum :: Hasql.Query.Query (Int64, Int64) Int64
selectSum =
  Hasql.Query.Query sql encoder decoder True
  where
    sql =
      "select ($1 + $2)"
    encoder =
      contramap fst (Hasql.Encoders.value Hasql.Encoders.int8) <>
      contramap snd (Hasql.Encoders.value Hasql.Encoders.int8)
    decoder =
      Hasql.Decoders.singleRow (Hasql.Decoders.value Hasql.Decoders.int8)

The statement above accepts a product of two parameters of type Int64 and produces a single result of type Int64.

Constructors

Query ByteString (Params a) (Result b) Bool 

Instances

Profunctor Query Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Query b c -> Query a d #

lmap :: (a -> b) -> Query b c -> Query a c #

rmap :: (b -> c) -> Query a b -> Query a c #

(#.) :: Coercible * c b => (b -> c) -> Query a b -> Query a c #

(.#) :: Coercible * b a => Query b c -> (a -> b) -> Query a c #

Functor (Query a) Source # 

Methods

fmap :: (a -> b) -> Query a a -> Query a b #

(<$) :: a -> Query a b -> Query a a #