module Hasql.Statement
  ( Statement (..),
    refineResult,

    -- * Recipes

    -- ** Insert many
    -- $insertMany

    -- ** IN and NOT IN
    -- $inAndNotIn
  )
where

import Hasql.Decoders qualified as Decoders
import Hasql.Decoders.All qualified as Decoders
import Hasql.Encoders qualified as Encoders
import Hasql.Prelude

-- |
-- 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.'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 params result
  = 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 params)
      -- | Decoder of result.
      (Decoders.Result result)
      -- | 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 params) where
  {-# INLINE fmap #-}
  fmap :: forall a b. (a -> b) -> Statement params a -> Statement params b
fmap = (a -> b) -> Statement params a -> Statement params b
forall b c a. (b -> c) -> Statement a b -> Statement a c
forall (p :: * -> * -> *) b c a.
Profunctor p =>
(b -> c) -> p a b -> p a c
rmap

instance Profunctor Statement where
  {-# INLINE dimap #-}
  dimap :: forall a b c d.
(a -> b) -> (c -> d) -> Statement b c -> Statement a d
dimap a -> b
f1 c -> d
f2 (Statement ByteString
template Params b
encoder Result c
decoder Bool
preparable) =
    ByteString -> Params a -> Result d -> Bool -> Statement a d
forall params result.
ByteString
-> Params params
-> Result result
-> Bool
-> Statement params result
Statement ByteString
template ((a -> b) -> Params b -> Params a
forall a' a. (a' -> a) -> Params a -> Params a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap a -> b
f1 Params b
encoder) ((c -> d) -> Result c -> Result d
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap c -> d
f2 Result c
decoder) Bool
preparable

-- |
-- 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>.
refineResult :: (a -> Either Text b) -> Statement params a -> Statement params b
refineResult :: forall a b params.
(a -> Either Text b) -> Statement params a -> Statement params b
refineResult a -> Either Text b
refiner (Statement ByteString
template Params params
encoder Result a
decoder Bool
preparable) =
  ByteString
-> Params params -> Result b -> Bool -> Statement params b
forall params result.
ByteString
-> Params params
-> Result result
-> Bool
-> Statement params result
Statement ByteString
template Params params
encoder ((a -> Either Text b) -> Result a -> Result b
forall a b. (a -> Either Text b) -> Result a -> Result b
Decoders.refineResult a -> Either Text b
refiner Result a
decoder) Bool
preparable

-- $insertMany
--
-- 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.'Data.Vector.unzip3' '>$<'
--         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.

-- $inAndNotIn
--
-- 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
-- <https://www.postgresql.org/docs/9.6/static/functions-comparisons.html#AEN20944 the PostgreSQL docs>.