hasql-1.4.5.2: An efficient PostgreSQL driver with a flexible mapping API
Safe HaskellNone
LanguageHaskell2010

Hasql.Statement

Synopsis

Documentation

data Statement a b Source #

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 a positional notation, as in the following: $1, $2, $3 and etc. Those references must be used in accordance to the order in which the according value encoders are specified in Params.

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

selectSum :: Statement (Int64, Int64) Int64
selectSum = Statement sql encoder decoder True where
  sql = "select ($1 + $2)"
  encoder =
    (fst >$< Encoders.param (Encoders.nonNullable Encoders.int8)) <>
    (snd >$< Encoders.param (Encoders.nullable Encoders.text))
  decoder = Decoders.singleRow (Decoders.column (Decoders.nonNullable Decoders.int8))

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

Constructors

Statement ByteString (Params a) (Result b) Bool 

Instances

Instances details
Profunctor Statement Source # 
Instance details

Defined in Hasql.Statement

Methods

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

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

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

(#.) :: forall a b c q. Coercible c b => q b c -> Statement a b -> Statement a c #

(.#) :: forall a b c q. Coercible b a => Statement b c -> q a b -> Statement a c #

Functor (Statement a) Source # 
Instance details

Defined in Hasql.Statement

Methods

fmap :: (a0 -> b) -> Statement a a0 -> Statement a b #

(<$) :: a0 -> Statement a b -> Statement a a0 #

refineResult :: (a -> Either Text b) -> Statement params a -> Statement params b Source #

Refine a result of a statement, causing the running session to fail with the UnexpectedResult error in case of refinement failure.

This function is especially useful for refining the results of statements produced with the "hasql-th" library.

Recipies

Insert many

It is not currently possible to pass in an array of encodable values to use in an insert many statement. Instead, PostgreSQL's (9.4 or later) unnest function can be used 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 =
        Encoders.param .
        Encoders.nonNullable .
        Encoders.array .
        Encoders.dimension foldl' .
        Encoders.element .
        Encoders.nonNullable
  decoder = Decoders.noResult

This approach is much more efficient than executing a single-row Insert statement multiple times.

IN and NOT IN

There is a common misconception that Postgresql supports array as a parameter for the IN operator. However Postgres only supports a syntactical list of values with it, i.e., you have to specify each option as an individual parameter (something IN ($1, $2, $3)).

Clearly it would be much more convenient to provide an array as a single parameter, but the IN operator does not support that. Fortunately, Postgres does provide such functionality with other operators:

  • Use something = ANY($1) instead of something IN ($1)
  • Use something <> ALL($1) instead of something NOT IN ($1)

For details see the Postgresql docs.