hasql-1.6.4.4: An efficient PostgreSQL driver with a flexible mapping API
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hasql.Statement

Synopsis

Documentation

data Statement params result Source #

Specification of a strictly single-statement query, which can be parameterized and prepared. It encapsulates the mapping of parameters and results in association with an SQL template.

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.nonNullable Encoders.int8))
    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 

Fields

  • ByteString

    SQL template.

    Must be formatted according to the Postgres standard, with any non-ASCII characters of the template encoded using UTF-8. The parameters must be referred to using the positional notation, as in the following: $1, $2, $3 and etc. These references must be used in accordance with the order in which the value encoders are specified in the parameters encoder.

  • (Params params)

    Parameters encoder.

  • (Result result)

    Decoder of result.

  • Bool

    Flag, determining whether it should be prepared.

    Set it to True if your application has a limited amount of queries and doesn't generate the SQL dynamically. This will boost the performance by allowing Postgres to avoid reconstructing the execution plan each time the query gets executed.

    Note that if you're using proxying applications like pgbouncer, such tools may be incompatible with prepared statements. So do consult their docs or just set it to False to stay on the safe side. It should be noted that starting from version 1.21.0 pgbouncer now does provide support for prepared statements.

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 params) Source # 
Instance details

Defined in Hasql.Statement

Methods

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

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

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

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

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

Recipes

Insert many

Starting from PostgreSQL 9.4 there is an unnest function which we can use in an analogous way to haskell's zip to pass in multiple arrays of values to be zipped into the rows to insert as in the following example:

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 =
      Data.Vector.unzip3 >$<
        Contravariant.Extras.contrazip3
          (Encoders.param $ Encoders.nonNullable $ Encoders.foldableArray $ Encoders.nonNullable Encoders.uuid)
          (Encoders.param $ Encoders.nonNullable $ Encoders.foldableArray $ Encoders.nonNullable Encoders.float8)
          (Encoders.param $ Encoders.nonNullable $ Encoders.foldableArray $ Encoders.nonNullable Encoders.float8)
    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 the 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. E.g., some_expression IN ($1, $2, $3).

Fortunately, Postgres does provide the expected functionality for arrays with other operators:

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

For details refer to the PostgreSQL docs.