Skip to content

Commit

Permalink
Update and correct the docs
Browse files Browse the repository at this point in the history
  • Loading branch information
nikita-volkov committed Mar 23, 2024
1 parent 4a78d16 commit ccf4f39
Showing 1 changed file with 61 additions and 56 deletions.
117 changes: 61 additions & 56 deletions library/Hasql/Statement.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module Hasql.Statement
( Statement (..),
refineResult,

-- * Recipies
-- * Recipes

-- ** Insert many
-- $insertMany
Expand All @@ -18,39 +18,50 @@ import qualified Hasql.Encoders as Encoders
import Hasql.Prelude

-- |
-- 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 with the order in which
-- the value encoders are specified in 'Encoders.Params'.
-- Specification of a strictly single-statement query, which can be parameterized and prepared, encapsulating the mapping of parameters and results.
--
-- 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.'Hasql.Encoders.param' (Encoders.'Hasql.Encoders.nonNullable' Encoders.'Hasql.Encoders.int8')) '<>'
-- ('snd' '>$<' Encoders.'Hasql.Encoders.param' (Encoders.'Hasql.Encoders.nonNullable' Encoders.'Hasql.Encoders.int8'))
-- decoder = Decoders.'Hasql.Decoders.singleRow' (Decoders.'Hasql.Decoders.column' (Decoders.'Hasql.Decoders.nonNullable' Decoders.'Hasql.Decoders.int8'))
-- selectSum =
-- 'Statement' sql encoder decoder True
-- where
-- sql =
-- \"select ($1 + $2)\"
-- encoder =
-- ('fst' '>$<' Encoders.'Hasql.Encoders.param' (Encoders.'Hasql.Encoders.nonNullable' Encoders.'Hasql.Encoders.int8')) '<>'
-- ('snd' '>$<' Encoders.'Hasql.Encoders.param' (Encoders.'Hasql.Encoders.nonNullable' Encoders.'Hasql.Encoders.int8'))
-- decoder =
-- Decoders.'Hasql.Decoders.singleRow' (Decoders.'Hasql.Decoders.column' (Decoders.'Hasql.Decoders.nonNullable' Decoders.'Hasql.Decoders.int8'))
-- @
--
-- The statement above accepts a product of two parameters of type 'Int64'
-- and produces a single result of type 'Int64'.
data Statement a b
= Statement ByteString (Encoders.Params a) (Decoders.Result b) Bool
= Statement
-- | 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.
ByteString
-- | Parameters encoder.
(Encoders.Params a)
-- | Decoder of result.
(Decoders.Result b)
-- | 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.
Bool

instance Functor (Statement a) where
{-# INLINE fmap #-}
Expand All @@ -62,8 +73,8 @@ instance Profunctor Statement where
Statement template (contramap f1 encoder) (fmap f2 decoder) preparable

-- |
-- Refine a result of a statement,
-- causing the running session to fail with the `UnexpectedResult` error in case of refinement failure.
-- 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
-- <http://hackage.haskell.org/package/hasql-th the \"hasql-th\" library>.
Expand All @@ -73,47 +84,41 @@ refineResult refiner (Statement template encoder decoder preparable) =

-- $insertMany
--
-- 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:
-- 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 =
-- contramap Vector.'Data.Vector.unzip3' $
-- contrazip3 (vector Encoders.'Encoders.uuid') (vector Encoders.'Encoders.float8') (vector Encoders.'Encoders.float8')
-- where
-- vector =
-- Encoders.'Encoders.param' .
-- Encoders.'Encoders.nonNullable' .
-- Encoders.'Encoders.array' .
-- Encoders.'Encoders.dimension' 'foldl'' .
-- Encoders.'Encoders.element' .
-- Encoders.'Encoders.nonNullable'
-- decoder = Decoders.'Decoders.noResult'
-- insertMultipleLocations =
-- 'Statement' sql encoder decoder True
-- where
-- sql =
-- "insert into location (id, x, y) select * from unnest ($1, $2, $3)"
-- encoder =
-- Data.Vector.'Data.Vector.unzip3' '>$<'
-- Contravariant.Extras.'Contravariant.Extras.contrazip3'
-- (Encoders.'Encoders.param' $ Encoders.'Encoders.nonNullable' $ Encoders.'Encoders.foldableArray' $ Encoders.'Encoders.nonNullable' Encoders.'Encoders.uuid')
-- (Encoders.'Encoders.param' $ Encoders.'Encoders.nonNullable' $ Encoders.'Encoders.foldableArray' $ Encoders.'Encoders.nonNullable' Encoders.'Encoders.float8')
-- (Encoders.'Encoders.param' $ Encoders.'Encoders.nonNullable' $ Encoders.'Encoders.foldableArray' $ Encoders.'Encoders.nonNullable' Encoders.'Encoders.float8')
-- decoder =
-- Decoders.'Decoders.noResult'
-- @
--
-- This approach is much more efficient than executing a single-row Insert
-- statement multiple times.
-- This approach is much more efficient than executing a single-row insert-statement multiple times.

-- $inAndNotIn
--
-- There is a common misconception that Postgresql supports array
-- as a parameter for the @IN@ operator.
-- 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
-- (@something IN ($1, $2, $3)@).
-- i.e., you have to specify each option as an individual parameter.
-- E.g., @some_expression 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:
-- Fortunately, Postgres does provide the expected functionality for arrays 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
-- <https://www.postgresql.org/docs/9.6/static/functions-comparisons.html#AEN20944 the Postgresql docs>.
-- For details refer to
-- <https://www.postgresql.org/docs/9.6/static/functions-comparisons.html#AEN20944 the PostgreSQL docs>.

0 comments on commit ccf4f39

Please sign in to comment.