{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}

------------------------------------------------------------------------------
-- |
-- Module:      Database.PostgreSQL.Simple
-- Copyright:   (c) 2011 MailRank, Inc.
--              (c) 2011-2012 Leon P Smith
-- License:     BSD3
-- Maintainer:  Leon P Smith <leon@melding-monads.com>
-- Stability:   experimental
--
-- A mid-level client library for the PostgreSQL database, aimed at ease of
-- use and high performance.
--
------------------------------------------------------------------------------

module Database.PostgreSQL.Simple
    (
    -- * Writing queries
    -- $use

    -- ** The Query type
    -- $querytype

    -- ** Parameter substitution
    -- $subst

    -- *** Type inference
    -- $inference

    -- ** Substituting a single parameter
    -- $only_param

    -- ** Representing a list of values
    -- $in

    -- ** Modifying multiple rows at once
    -- $many

    -- ** @RETURNING@: modifications that return results
    -- $returning

    -- * Extracting results
    -- $result

    -- ** Handling null values
    -- $null

    -- ** Type conversions
    -- $types

    -- * Types
      Connection
    , Query
    , ToRow
    , FromRow
    , In(..)
    , Binary(..)
    , Only(..)
    , (:.)(..)
    -- ** Exceptions
    , SqlError(..)
    , PQ.ExecStatus(..)
    , FormatError(..)
    , QueryError(..)
    , ResultError(..)
    -- * Connection management
    , Base.connectPostgreSQL
    , Base.close
    , Base.connect
    , Base.ConnectInfo(..)
    , Base.defaultConnectInfo
    , Base.postgreSQLConnectionString
    -- * Queries that return results
    , query
    , query_
    -- ** Queries taking parser as argument
    , queryWith
    , queryWith_
    -- * Queries that stream results
    , FoldOptions(..)
    , FetchQuantity(..)
    , defaultFoldOptions
    , fold
    , foldWithOptions
    , fold_
    , foldWithOptions_
    , forEach
    , forEach_
    , returning
    -- ** Queries that stream results taking a parser as an argument
    , foldWith
    , foldWithOptionsAndParser
    , foldWith_
    , foldWithOptionsAndParser_
    , forEachWith
    , forEachWith_
    , returningWith
    -- * Statements that do not return results
    , execute
    , execute_
    , executeMany
--    , Base.insertID
    -- * Transaction handling
    , withTransaction
    , withSavepoint
--    , Base.autocommit
    , begin
    , commit
    , rollback
    -- * Helper functions
    , formatMany
    , formatQuery
    ) where

import           Data.ByteString.Builder (Builder, byteString, char8)
import           Control.Applicative ((<$>))
import           Control.Exception as E
import           Data.ByteString (ByteString)
import           Data.Int (Int64)
import           Data.List (intersperse)
import           Data.Monoid (mconcat)
import           Database.PostgreSQL.Simple.Compat ((<>), toByteString)
import           Database.PostgreSQL.Simple.Cursor
import           Database.PostgreSQL.Simple.FromField (ResultError(..))
import           Database.PostgreSQL.Simple.FromRow (FromRow(..))
import           Database.PostgreSQL.Simple.ToField (Action(..))
import           Database.PostgreSQL.Simple.ToRow (ToRow(..))
import           Database.PostgreSQL.Simple.Types
                   ( Binary(..), In(..), Only(..), Query(..), (:.)(..) )
import           Database.PostgreSQL.Simple.Internal as Base
import           Database.PostgreSQL.Simple.Internal.PQResultUtils
import           Database.PostgreSQL.Simple.Transaction
import qualified Database.PostgreSQL.LibPQ as PQ
import qualified Data.ByteString.Char8 as B


-- | Format a query string.
--
-- This function is exposed to help with debugging and logging. Do not
-- use it to prepare queries for execution.
--
-- String parameters are escaped according to the character set in use
-- on the 'Connection'.
--
-- Throws 'FormatError' if the query string could not be formatted
-- correctly.
formatQuery :: ToRow q => Connection -> Query -> q -> IO ByteString
formatQuery :: Connection -> Query -> q -> IO ByteString
formatQuery Connection
conn q :: Query
q@(Query ByteString
template) q
qs
    | [Action] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Action]
xs Bool -> Bool -> Bool
&& Char
'?' Char -> ByteString -> Bool
`B.notElem` ByteString
template = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
template
    | Bool
otherwise = Builder -> ByteString
toByteString (Builder -> ByteString) -> IO Builder -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> Query -> ByteString -> [Action] -> IO Builder
buildQuery Connection
conn Query
q ByteString
template [Action]
xs
  where xs :: [Action]
xs = q -> [Action]
forall a. ToRow a => a -> [Action]
toRow q
qs

-- | Format a query string with a variable number of rows.
--
-- This function is exposed to help with debugging and logging. Do not
-- use it to prepare queries for execution.
--
-- The query string must contain exactly one substitution group,
-- identified by the SQL keyword \"@VALUES@\" (case insensitive)
-- followed by an \"@(@\" character, a series of one or more \"@?@\"
-- characters separated by commas, and a \"@)@\" character. White
-- space in a substitution group is permitted.
--
-- Throws 'FormatError' if the query string could not be formatted
-- correctly.
formatMany :: (ToRow q) => Connection -> Query -> [q] -> IO ByteString
formatMany :: Connection -> Query -> [q] -> IO ByteString
formatMany Connection
_ Query
q [] = String -> Query -> [Action] -> IO ByteString
forall a. String -> Query -> [Action] -> a
fmtError String
"no rows supplied" Query
q []
formatMany Connection
conn q :: Query
q@(Query ByteString
template) [q]
qs = do
  case ByteString -> Maybe (ByteString, ByteString, ByteString)
parseTemplate ByteString
template of
    Just (ByteString
before, ByteString
qbits, ByteString
after) -> do
      [Builder]
bs <- (q -> IO Builder) -> [q] -> IO [Builder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Connection -> Query -> ByteString -> [Action] -> IO Builder
buildQuery Connection
conn Query
q ByteString
qbits ([Action] -> IO Builder) -> (q -> [Action]) -> q -> IO Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. q -> [Action]
forall a. ToRow a => a -> [Action]
toRow) [q]
qs
      ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString)
-> ([Builder] -> ByteString) -> [Builder] -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
toByteString (Builder -> ByteString)
-> ([Builder] -> Builder) -> [Builder] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> IO ByteString) -> [Builder] -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Builder
byteString ByteString
before Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
:
                                        Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
intersperse (Char -> Builder
char8 Char
',') [Builder]
bs [Builder] -> [Builder] -> [Builder]
forall a. [a] -> [a] -> [a]
++
                                        [ByteString -> Builder
byteString ByteString
after]
    Maybe (ByteString, ByteString, ByteString)
Nothing -> String -> Query -> [Action] -> IO ByteString
forall a. String -> Query -> [Action] -> a
fmtError String
"syntax error in multi-row template" Query
q []

-- Split the input string into three pieces, @before@, @qbits@, and @after@,
-- following this grammar:
--
-- start: ^ before qbits after $
--     before: ([^?]* [^?\w])? 'VALUES' \s*
--     qbits:  '(' \s* '?' \s* (',' \s* '?' \s*)* ')'
--     after:  [^?]*
--
-- \s: [ \t\n\r\f]
-- \w: [A-Z] | [a-z] | [\x80-\xFF] | '_' | '$' | [0-9]
--
-- This would be much more concise with some sort of regex engine.
-- 'formatMany' used to use pcre-light instead of this hand-written parser,
-- but pcre is a hassle to install on Windows.
parseTemplate :: ByteString -> Maybe (ByteString, ByteString, ByteString)
parseTemplate :: ByteString -> Maybe (ByteString, ByteString, ByteString)
parseTemplate ByteString
template =
    -- Convert input string to uppercase, to facilitate searching.
    ByteString -> Maybe (ByteString, ByteString, ByteString)
search (ByteString -> Maybe (ByteString, ByteString, ByteString))
-> ByteString -> Maybe (ByteString, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> ByteString -> ByteString
B.map Char -> Char
toUpper_ascii ByteString
template
  where
    -- Search for the next occurrence of "VALUES"
    search :: ByteString -> Maybe (ByteString, ByteString, ByteString)
search ByteString
bs =
        case ByteString -> ByteString -> (ByteString, ByteString)
B.breakSubstring ByteString
"VALUES" ByteString
bs of
            (ByteString
x, ByteString
y)
                -- If "VALUES" is not present in the string, or any '?' characters
                -- were encountered prior to it, fail.
                | ByteString -> Bool
B.null ByteString
y Bool -> Bool -> Bool
|| (Char
'?' Char -> ByteString -> Bool
`B.elem` ByteString
x)
               -> Maybe (ByteString, ByteString, ByteString)
forall a. Maybe a
Nothing

                -- If "VALUES" is preceded by an identifier character (a.k.a. \w),
                -- try the next occurrence.
                | Bool -> Bool
not (ByteString -> Bool
B.null ByteString
x) Bool -> Bool -> Bool
&& Char -> Bool
isIdent (ByteString -> Char
B.last ByteString
x)
               -> ByteString -> Maybe (ByteString, ByteString, ByteString)
search (ByteString -> Maybe (ByteString, ByteString, ByteString))
-> ByteString -> Maybe (ByteString, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
B.drop Int
6 ByteString
y

                -- Otherwise, we have a legitimate "VALUES" token.
                | Bool
otherwise
               -> ByteString -> Maybe (ByteString, ByteString, ByteString)
parseQueryBits (ByteString -> Maybe (ByteString, ByteString, ByteString))
-> ByteString -> Maybe (ByteString, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
skipSpace (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
B.drop Int
6 ByteString
y

    -- Parse '(' \s* '?' \s* .  If this doesn't match
    -- (and we don't consume a '?'), look for another "VALUES".
    --
    -- qb points to the open paren (if present), meaning it points to the
    -- beginning of the "qbits" production described above.  This is why we
    -- pass it down to finishQueryBits.
    parseQueryBits :: ByteString -> Maybe (ByteString, ByteString, ByteString)
parseQueryBits ByteString
qb
        | Just (Char
'(', ByteString -> ByteString
skipSpace -> ByteString
bs1) <- ByteString -> Maybe (Char, ByteString)
B.uncons ByteString
qb
        , Just (Char
'?', ByteString -> ByteString
skipSpace -> ByteString
bs2) <- ByteString -> Maybe (Char, ByteString)
B.uncons ByteString
bs1
        = ByteString
-> ByteString -> Maybe (ByteString, ByteString, ByteString)
finishQueryBits ByteString
qb ByteString
bs2
        | Bool
otherwise
        = ByteString -> Maybe (ByteString, ByteString, ByteString)
search ByteString
qb

    -- Parse (',' \s* '?' \s*)* ')' [^?]* .
    --
    -- Since we've already consumed at least one '?', there's no turning back.
    -- The parse has to succeed here, or the whole thing fails
    -- (because we don't allow '?' to appear outside of the VALUES list).
    finishQueryBits :: ByteString
-> ByteString -> Maybe (ByteString, ByteString, ByteString)
finishQueryBits ByteString
qb ByteString
bs0
        | Just (Char
')', ByteString
bs1) <- ByteString -> Maybe (Char, ByteString)
B.uncons ByteString
bs0
        = if Char
'?' Char -> ByteString -> Bool
`B.elem` ByteString
bs1
              then Maybe (ByteString, ByteString, ByteString)
forall a. Maybe a
Nothing
              else (ByteString, ByteString, ByteString)
-> Maybe (ByteString, ByteString, ByteString)
forall a. a -> Maybe a
Just ((ByteString, ByteString, ByteString)
 -> Maybe (ByteString, ByteString, ByteString))
-> (ByteString, ByteString, ByteString)
-> Maybe (ByteString, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString
-> ByteString -> ByteString -> (ByteString, ByteString, ByteString)
slice3 ByteString
template ByteString
qb ByteString
bs1
        | Just (Char
',', ByteString -> ByteString
skipSpace -> ByteString
bs1) <- ByteString -> Maybe (Char, ByteString)
B.uncons ByteString
bs0
        , Just (Char
'?', ByteString -> ByteString
skipSpace -> ByteString
bs2) <- ByteString -> Maybe (Char, ByteString)
B.uncons ByteString
bs1
        = ByteString
-> ByteString -> Maybe (ByteString, ByteString, ByteString)
finishQueryBits ByteString
qb ByteString
bs2
        | Bool
otherwise
        = Maybe (ByteString, ByteString, ByteString)
forall a. Maybe a
Nothing

    -- Slice a string into three pieces, given the start offset of the second
    -- and third pieces.  Each "offset" is actually a tail of the uppercase
    -- version of the template string.  Its length is used to infer the offset.
    --
    -- It is important to note that we only slice the original template.
    -- We don't want our all-caps trick messing up the actual query string.
    slice3 :: ByteString
-> ByteString -> ByteString -> (ByteString, ByteString, ByteString)
slice3 ByteString
source ByteString
p1 ByteString
p2 =
        (ByteString
s1, ByteString
s2, ByteString
source'')
      where
        (ByteString
s1, ByteString
source')  = Int -> ByteString -> (ByteString, ByteString)
B.splitAt (ByteString -> Int
B.length ByteString
source Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
B.length ByteString
p1) ByteString
source
        (ByteString
s2, ByteString
source'') = Int -> ByteString -> (ByteString, ByteString)
B.splitAt (ByteString -> Int
B.length ByteString
p1     Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
B.length ByteString
p2) ByteString
source'

    toUpper_ascii :: Char -> Char
toUpper_ascii Char
c | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'z' = Int -> Char
forall a. Enum a => Int -> a
toEnum (Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
32)
                    | Bool
otherwise            = Char
c

    -- Based on the definition of {ident_cont} in src/backend/parser/scan.l
    -- in the PostgreSQL source.  No need to check [a-z], since we converted
    -- the whole string to uppercase.
    isIdent :: Char -> Bool
isIdent Char
c = (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0'    Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9')
             Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'A'    Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'Z')
             Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x80' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\xFF')
             Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
             Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'$'

    -- Based on {space} in scan.l
    isSpace_ascii :: Char -> Bool
isSpace_ascii Char
c = (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\t' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\r')

    skipSpace :: ByteString -> ByteString
skipSpace = (Char -> Bool) -> ByteString -> ByteString
B.dropWhile Char -> Bool
isSpace_ascii


buildQuery :: Connection -> Query -> ByteString -> [Action] -> IO Builder
buildQuery :: Connection -> Query -> ByteString -> [Action] -> IO Builder
buildQuery Connection
conn Query
q ByteString
template [Action]
xs =
    [Builder] -> [Builder] -> Builder
forall p. Semigroup p => [p] -> [p] -> p
zipParams (ByteString -> [Builder]
split ByteString
template) ([Builder] -> Builder) -> IO [Builder] -> IO Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Action -> IO Builder) -> [Action] -> IO [Builder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Connection -> Query -> [Action] -> Action -> IO Builder
buildAction Connection
conn Query
q [Action]
xs) [Action]
xs
  where split :: ByteString -> [Builder]
split ByteString
s =
            -- This part escapes double '??'s to make literal '?'s possible
            -- in PostgreSQL queries using the JSON operators: @?@, @?|@ and @?&@
            let (ByteString
h,ByteString
t) = ByteString -> (ByteString, ByteString)
breakOnSingleQuestionMark ByteString
s
            in ByteString -> Builder
byteString ByteString
h
               Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
: if ByteString -> Bool
B.null ByteString
t
                 then []
                 else ByteString -> [Builder]
split (ByteString -> ByteString
B.tail ByteString
t)
        zipParams :: [p] -> [p] -> p
zipParams (p
t:[p]
ts) (p
p:[p]
ps) = p
t p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> [p] -> [p] -> p
zipParams [p]
ts [p]
ps
        zipParams [p
t] []        = p
t
        zipParams [p]
_ [p]
_ = String -> Query -> [Action] -> p
forall a. String -> Query -> [Action] -> a
fmtError (Int -> String
forall a. Show a => a -> String
show Int
countSingleQs String -> String -> String
forall a. [a] -> [a] -> [a]
++
                                  String
" single '?' characters, but " String -> String -> String
forall a. [a] -> [a] -> [a]
++
                                  Int -> String
forall a. Show a => a -> String
show ([Action] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Action]
xs) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" parameters") Query
q [Action]
xs
        countSingleQs :: Int
countSingleQs = Int -> ByteString -> Int
go Int
0 ByteString
template
          where go :: Int -> ByteString -> Int
go Int
i ByteString
"" = (Int
i :: Int)
                go Int
i ByteString
bs = case (ByteString, ByteString)
qms of
                            (ByteString
"?",ByteString
"?") -> Int -> ByteString -> Int
go Int
i ByteString
nextQMBS
                            (ByteString
"?",ByteString
_) -> Int -> ByteString -> Int
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ByteString
nextQMBS
                            (ByteString, ByteString)
_ -> Int
i
                  where qms :: (ByteString, ByteString)
qms = Int -> ByteString -> (ByteString, ByteString)
B.splitAt Int
1 ByteString
qmBS
                        (ByteString
qmBS,ByteString
nextQMBS) = Int -> ByteString -> (ByteString, ByteString)
B.splitAt Int
2 ByteString
qmBS'
                        qmBS' :: ByteString
qmBS' = (Char -> Bool) -> ByteString -> ByteString
B.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'?') ByteString
bs

-- | Execute an @INSERT@, @UPDATE@, or other SQL query that is not
-- expected to return results.
--
-- Returns the number of rows affected.
--
-- Throws 'FormatError' if the query could not be formatted correctly, or
-- a 'SqlError' exception if the backend returns an error.
execute :: (ToRow q) => Connection -> Query -> q -> IO Int64
execute :: Connection -> Query -> q -> IO Int64
execute Connection
conn Query
template q
qs = do
  Result
result <- Connection -> ByteString -> IO Result
exec Connection
conn (ByteString -> IO Result) -> IO ByteString -> IO Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Connection -> Query -> q -> IO ByteString
forall q. ToRow q => Connection -> Query -> q -> IO ByteString
formatQuery Connection
conn Query
template q
qs
  Connection -> Query -> Result -> IO Int64
finishExecute Connection
conn Query
template Result
result

-- | Execute a multi-row @INSERT@, @UPDATE@, or other SQL query that is not
-- expected to return results.
--
-- Returns the number of rows affected.   If the list of parameters is empty,
-- this function will simply return 0 without issuing the query to the backend.
-- If this is not desired, consider using the 'Values' constructor instead.
--
-- Throws 'FormatError' if the query could not be formatted correctly, or
-- a 'SqlError' exception if the backend returns an error.
--
-- For example,  here's a command that inserts two rows into a table
-- with two columns:
--
-- @
-- executeMany c [sql|
--     INSERT INTO sometable VALUES (?,?)
--  |] [(1, \"hello\"),(2, \"world\")]
-- @
--
-- Here's an canonical example of a multi-row update command:
--
-- @
-- executeMany c [sql|
--     UPDATE sometable
--        SET y = upd.y
--       FROM (VALUES (?,?)) as upd(x,y)
--      WHERE sometable.x = upd.x
--  |] [(1, \"hello\"),(2, \"world\")]
-- @

executeMany :: (ToRow q) => Connection -> Query -> [q] -> IO Int64
executeMany :: Connection -> Query -> [q] -> IO Int64
executeMany Connection
_ Query
_ [] = Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
0
executeMany Connection
conn Query
q [q]
qs = do
  Result
result <- Connection -> ByteString -> IO Result
exec Connection
conn (ByteString -> IO Result) -> IO ByteString -> IO Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Connection -> Query -> [q] -> IO ByteString
forall q. ToRow q => Connection -> Query -> [q] -> IO ByteString
formatMany Connection
conn Query
q [q]
qs
  Connection -> Query -> Result -> IO Int64
finishExecute Connection
conn Query
q Result
result

-- | Execute @INSERT ... RETURNING@, @UPDATE ... RETURNING@, or other SQL
-- query that accepts multi-row input and is expected to return results.
-- Note that it is possible to write
--    @'query' conn "INSERT ... RETURNING ..." ...@
-- in cases where you are only inserting a single row,  and do not need
-- functionality analogous to 'executeMany'.
--
-- If the list of parameters is empty,  this function will simply return @[]@
-- without issuing the query to the backend.   If this is not desired,
-- consider using the 'Values' constructor instead.
--
-- Throws 'FormatError' if the query could not be formatted correctly.
returning :: (ToRow q, FromRow r) => Connection -> Query -> [q] -> IO [r]
returning :: Connection -> Query -> [q] -> IO [r]
returning = RowParser r -> Connection -> Query -> [q] -> IO [r]
forall q r.
ToRow q =>
RowParser r -> Connection -> Query -> [q] -> IO [r]
returningWith RowParser r
forall a. FromRow a => RowParser a
fromRow

-- | A version of 'returning' taking parser as argument
returningWith :: (ToRow q) => RowParser r -> Connection -> Query -> [q] -> IO [r]
returningWith :: RowParser r -> Connection -> Query -> [q] -> IO [r]
returningWith RowParser r
_ Connection
_ Query
_ [] = [r] -> IO [r]
forall (m :: * -> *) a. Monad m => a -> m a
return []
returningWith RowParser r
parser Connection
conn Query
q [q]
qs = do
  Result
result <- Connection -> ByteString -> IO Result
exec Connection
conn (ByteString -> IO Result) -> IO ByteString -> IO Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Connection -> Query -> [q] -> IO ByteString
forall q. ToRow q => Connection -> Query -> [q] -> IO ByteString
formatMany Connection
conn Query
q [q]
qs
  RowParser r -> Connection -> Query -> Result -> IO [r]
forall r. RowParser r -> Connection -> Query -> Result -> IO [r]
finishQueryWith RowParser r
parser Connection
conn Query
q Result
result

-- | Perform a @SELECT@ or other SQL query that is expected to return
-- results. All results are retrieved and converted before this
-- function returns.
--
-- When processing large results, this function will consume a lot of
-- client-side memory.  Consider using 'fold' instead.
--
-- Exceptions that may be thrown:
--
-- * 'FormatError': the query string could not be formatted correctly.
--
-- * 'QueryError': the result contains no columns (i.e. you should be
--   using 'execute' instead of 'query').
--
-- * 'ResultError': result conversion failed.
--
-- * 'SqlError':  the postgresql backend returned an error,  e.g.
--   a syntax or type error,  or an incorrect table or column name.
query :: (ToRow q, FromRow r) => Connection -> Query -> q -> IO [r]
query :: Connection -> Query -> q -> IO [r]
query = RowParser r -> Connection -> Query -> q -> IO [r]
forall q r.
ToRow q =>
RowParser r -> Connection -> Query -> q -> IO [r]
queryWith RowParser r
forall a. FromRow a => RowParser a
fromRow

-- | A version of 'query' that does not perform query substitution.
query_ :: (FromRow r) => Connection -> Query -> IO [r]
query_ :: Connection -> Query -> IO [r]
query_ = RowParser r -> Connection -> Query -> IO [r]
forall r. RowParser r -> Connection -> Query -> IO [r]
queryWith_ RowParser r
forall a. FromRow a => RowParser a
fromRow

-- | A version of 'query' taking parser as argument
queryWith :: ToRow q => RowParser r -> Connection -> Query -> q -> IO [r]
queryWith :: RowParser r -> Connection -> Query -> q -> IO [r]
queryWith RowParser r
parser Connection
conn Query
template q
qs = do
  Result
result <- Connection -> ByteString -> IO Result
exec Connection
conn (ByteString -> IO Result) -> IO ByteString -> IO Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Connection -> Query -> q -> IO ByteString
forall q. ToRow q => Connection -> Query -> q -> IO ByteString
formatQuery Connection
conn Query
template q
qs
  RowParser r -> Connection -> Query -> Result -> IO [r]
forall r. RowParser r -> Connection -> Query -> Result -> IO [r]
finishQueryWith RowParser r
parser Connection
conn Query
template Result
result

-- | A version of 'query_' taking parser as argument
queryWith_ :: RowParser r -> Connection -> Query -> IO [r]
queryWith_ :: RowParser r -> Connection -> Query -> IO [r]
queryWith_ RowParser r
parser Connection
conn q :: Query
q@(Query ByteString
que) = do
  Result
result <- Connection -> ByteString -> IO Result
exec Connection
conn ByteString
que
  RowParser r -> Connection -> Query -> Result -> IO [r]
forall r. RowParser r -> Connection -> Query -> Result -> IO [r]
finishQueryWith RowParser r
parser Connection
conn Query
q Result
result

-- | Perform a @SELECT@ or other SQL query that is expected to return
-- results. Results are streamed incrementally from the server, and
-- consumed via a left fold.
--
-- When dealing with small results, it may be simpler (and perhaps
-- faster) to use 'query' instead.
--
-- This fold is /not/ strict. The stream consumer is responsible for
-- forcing the evaluation of its result to avoid space leaks.
--
-- This is implemented using a database cursor.    As such,  this requires
-- a transaction.   This function will detect whether or not there is a
-- transaction in progress,  and will create a 'ReadCommitted' 'ReadOnly'
-- transaction if needed.   The cursor is given a unique temporary name,
-- so the consumer may itself call fold.
--
-- Exceptions that may be thrown:
--
-- * 'FormatError': the query string could not be formatted correctly.
--
-- * 'QueryError': the result contains no columns (i.e. you should be
--   using 'execute' instead of 'query').
--
-- * 'ResultError': result conversion failed.
--
-- * 'SqlError':  the postgresql backend returned an error,  e.g.
--   a syntax or type error,  or an incorrect table or column name.
fold            :: ( FromRow row, ToRow params )
                => Connection
                -> Query
                -> params
                -> a
                -> (a -> row -> IO a)
                -> IO a
fold :: Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
fold = FoldOptions
-> Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
forall row params a.
(FromRow row, ToRow params) =>
FoldOptions
-> Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
foldWithOptions FoldOptions
defaultFoldOptions

-- | A version of 'fold' taking a parser as an argument
foldWith        :: ( ToRow params )
                => RowParser row
                -> Connection
                -> Query
                -> params
                -> a
                -> (a -> row -> IO a)
                -> IO a
foldWith :: RowParser row
-> Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
foldWith = FoldOptions
-> RowParser row
-> Connection
-> Query
-> params
-> a
-> (a -> row -> IO a)
-> IO a
forall params row a.
ToRow params =>
FoldOptions
-> RowParser row
-> Connection
-> Query
-> params
-> a
-> (a -> row -> IO a)
-> IO a
foldWithOptionsAndParser FoldOptions
defaultFoldOptions

-- | Number of rows to fetch at a time.   'Automatic' currently defaults
--   to 256 rows,  although it might be nice to make this more intelligent
--   based on e.g. the average size of the rows.
data FetchQuantity
   = Automatic
   | Fixed !Int

data FoldOptions
   = FoldOptions {
       FoldOptions -> FetchQuantity
fetchQuantity   :: !FetchQuantity,
       FoldOptions -> TransactionMode
transactionMode :: !TransactionMode
     }

-- | defaults to 'Automatic',  and 'TransactionMode' 'ReadCommitted' 'ReadOnly'
defaultFoldOptions :: FoldOptions
defaultFoldOptions :: FoldOptions
defaultFoldOptions = FoldOptions :: FetchQuantity -> TransactionMode -> FoldOptions
FoldOptions {
      fetchQuantity :: FetchQuantity
fetchQuantity   = FetchQuantity
Automatic,
      transactionMode :: TransactionMode
transactionMode = IsolationLevel -> ReadWriteMode -> TransactionMode
TransactionMode IsolationLevel
ReadCommitted ReadWriteMode
ReadOnly
    }

-- | The same as 'fold',  but this provides a bit more control over
--   lower-level details.  Currently,  the number of rows fetched per
--   round-trip to the server and the transaction mode may be adjusted
--   accordingly.    If the connection is already in a transaction,
--   then the existing transaction is used and thus the 'transactionMode'
--   option is ignored.
foldWithOptions :: ( FromRow row, ToRow params )
                => FoldOptions
                -> Connection
                -> Query
                -> params
                -> a
                -> (a -> row -> IO a)
                -> IO a
foldWithOptions :: FoldOptions
-> Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
foldWithOptions FoldOptions
opts = FoldOptions
-> RowParser row
-> Connection
-> Query
-> params
-> a
-> (a -> row -> IO a)
-> IO a
forall params row a.
ToRow params =>
FoldOptions
-> RowParser row
-> Connection
-> Query
-> params
-> a
-> (a -> row -> IO a)
-> IO a
foldWithOptionsAndParser FoldOptions
opts RowParser row
forall a. FromRow a => RowParser a
fromRow

-- | A version of 'foldWithOptions' taking a parser as an argument
foldWithOptionsAndParser :: (ToRow params)
                         => FoldOptions
                         -> RowParser row
                         -> Connection
                         -> Query
                         -> params
                         -> a
                         -> (a -> row -> IO a)
                         -> IO a
foldWithOptionsAndParser :: FoldOptions
-> RowParser row
-> Connection
-> Query
-> params
-> a
-> (a -> row -> IO a)
-> IO a
foldWithOptionsAndParser FoldOptions
opts RowParser row
parser Connection
conn Query
template params
qs a
a a -> row -> IO a
f = do
    ByteString
q <- Connection -> Query -> params -> IO ByteString
forall q. ToRow q => Connection -> Query -> q -> IO ByteString
formatQuery Connection
conn Query
template params
qs
    FoldOptions
-> RowParser row
-> Connection
-> Query
-> Query
-> a
-> (a -> row -> IO a)
-> IO a
forall row a.
FoldOptions
-> RowParser row
-> Connection
-> Query
-> Query
-> a
-> (a -> row -> IO a)
-> IO a
doFold FoldOptions
opts RowParser row
parser Connection
conn Query
template (ByteString -> Query
Query ByteString
q) a
a a -> row -> IO a
f

-- | A version of 'fold' that does not perform query substitution.
fold_ :: (FromRow r) =>
         Connection
      -> Query                  -- ^ Query.
      -> a                      -- ^ Initial state for result consumer.
      -> (a -> r -> IO a)       -- ^ Result consumer.
      -> IO a
fold_ :: Connection -> Query -> a -> (a -> r -> IO a) -> IO a
fold_ = FoldOptions -> Connection -> Query -> a -> (a -> r -> IO a) -> IO a
forall r a.
FromRow r =>
FoldOptions -> Connection -> Query -> a -> (a -> r -> IO a) -> IO a
foldWithOptions_ FoldOptions
defaultFoldOptions

-- | A version of 'fold_' taking a parser as an argument
foldWith_ :: RowParser r
          -> Connection
          -> Query
          -> a
          -> (a -> r -> IO a)
          -> IO a
foldWith_ :: RowParser r -> Connection -> Query -> a -> (a -> r -> IO a) -> IO a
foldWith_ = FoldOptions
-> RowParser r
-> Connection
-> Query
-> a
-> (a -> r -> IO a)
-> IO a
forall r a.
FoldOptions
-> RowParser r
-> Connection
-> Query
-> a
-> (a -> r -> IO a)
-> IO a
foldWithOptionsAndParser_ FoldOptions
defaultFoldOptions

foldWithOptions_ :: (FromRow r) =>
                    FoldOptions
                 -> Connection
                 -> Query             -- ^ Query.
                 -> a                 -- ^ Initial state for result consumer.
                 -> (a -> r -> IO a)  -- ^ Result consumer.
                 -> IO a
foldWithOptions_ :: FoldOptions -> Connection -> Query -> a -> (a -> r -> IO a) -> IO a
foldWithOptions_ FoldOptions
opts Connection
conn Query
query' a
a a -> r -> IO a
f = FoldOptions
-> RowParser r
-> Connection
-> Query
-> Query
-> a
-> (a -> r -> IO a)
-> IO a
forall row a.
FoldOptions
-> RowParser row
-> Connection
-> Query
-> Query
-> a
-> (a -> row -> IO a)
-> IO a
doFold FoldOptions
opts RowParser r
forall a. FromRow a => RowParser a
fromRow Connection
conn Query
query' Query
query' a
a a -> r -> IO a
f

-- | A version of 'foldWithOptions_' taking a parser as an argument
foldWithOptionsAndParser_ :: FoldOptions
                          -> RowParser r
                          -> Connection
                          -> Query             -- ^ Query.
                          -> a                 -- ^ Initial state for result consumer.
                          -> (a -> r -> IO a)  -- ^ Result consumer.
                          -> IO a
foldWithOptionsAndParser_ :: FoldOptions
-> RowParser r
-> Connection
-> Query
-> a
-> (a -> r -> IO a)
-> IO a
foldWithOptionsAndParser_ FoldOptions
opts RowParser r
parser Connection
conn Query
query' a
a a -> r -> IO a
f = FoldOptions
-> RowParser r
-> Connection
-> Query
-> Query
-> a
-> (a -> r -> IO a)
-> IO a
forall row a.
FoldOptions
-> RowParser row
-> Connection
-> Query
-> Query
-> a
-> (a -> row -> IO a)
-> IO a
doFold FoldOptions
opts RowParser r
parser Connection
conn Query
query' Query
query' a
a a -> r -> IO a
f

doFold :: FoldOptions
       -> RowParser row
       -> Connection
       -> Query
       -> Query
       -> a
       -> (a -> row -> IO a)
       -> IO a
doFold :: FoldOptions
-> RowParser row
-> Connection
-> Query
-> Query
-> a
-> (a -> row -> IO a)
-> IO a
doFold FoldOptions{TransactionMode
FetchQuantity
transactionMode :: TransactionMode
fetchQuantity :: FetchQuantity
transactionMode :: FoldOptions -> TransactionMode
fetchQuantity :: FoldOptions -> FetchQuantity
..} RowParser row
parser Connection
conn Query
_template Query
q a
a0 a -> row -> IO a
f = do
    TransactionStatus
stat <- Connection
-> (Connection -> IO TransactionStatus) -> IO TransactionStatus
forall a. Connection -> (Connection -> IO a) -> IO a
withConnection Connection
conn Connection -> IO TransactionStatus
PQ.transactionStatus
    case TransactionStatus
stat of
      TransactionStatus
PQ.TransIdle    -> TransactionMode -> Connection -> IO a -> IO a
forall a. TransactionMode -> Connection -> IO a -> IO a
withTransactionMode TransactionMode
transactionMode Connection
conn IO a
go
      TransactionStatus
PQ.TransInTrans -> IO a
go
      TransactionStatus
PQ.TransActive  -> String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"foldWithOpts FIXME:  PQ.TransActive"
         -- This _shouldn't_ occur in the current incarnation of
         -- the library,  as we aren't using libpq asynchronously.
         -- However,  it could occur in future incarnations of
         -- this library or if client code uses the Internal module
         -- to use raw libpq commands on postgresql-simple connections.
      TransactionStatus
PQ.TransInError -> String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"foldWithOpts FIXME:  PQ.TransInError"
         -- This should be turned into a better error message.
         -- It is probably a bad idea to automatically roll
         -- back the transaction and start another.
      TransactionStatus
PQ.TransUnknown -> String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"foldWithOpts FIXME:  PQ.TransUnknown"
         -- Not sure what this means.
  where
    declare :: IO Cursor
declare =
      Connection -> Query -> IO Cursor
declareCursor Connection
conn Query
q
    fetch :: Cursor -> a -> IO (Either a a)
fetch Cursor
cursor a
a =
      Cursor
-> RowParser row
-> Int
-> (a -> row -> IO a)
-> a
-> IO (Either a a)
forall r a.
Cursor
-> RowParser r -> Int -> (a -> r -> IO a) -> a -> IO (Either a a)
foldForwardWithParser Cursor
cursor RowParser row
parser Int
chunkSize a -> row -> IO a
f a
a

    go :: IO a
go = IO Cursor -> (Cursor -> IO ()) -> (Cursor -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Cursor
declare Cursor -> IO ()
closeCursor ((Cursor -> IO a) -> IO a) -> (Cursor -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Cursor
cursor ->
             let loop :: a -> IO a
loop a
a = Cursor -> a -> IO (Either a a)
fetch Cursor
cursor a
a IO (Either a a) -> (Either a a -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                            \Either a a
r -> case Either a a
r of
                                    Left a
x -> a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
                                    Right a
x -> a -> IO a
loop a
x
               in a -> IO a
loop a
a0

-- FIXME: choose the Automatic chunkSize more intelligently
--   One possibility is to use the type of the results,  although this
--   still isn't a perfect solution, given that common types (e.g. text)
--   are of highly variable size.
--   A refinement of this technique is to pick this number adaptively
--   as results are read in from the database.
    chunkSize :: Int
chunkSize = case FetchQuantity
fetchQuantity of
                 FetchQuantity
Automatic   -> Int
256
                 Fixed Int
n     -> Int
n

-- | A version of 'fold' that does not transform a state value.
forEach :: (ToRow q, FromRow r) =>
           Connection
        -> Query                -- ^ Query template.
        -> q                    -- ^ Query parameters.
        -> (r -> IO ())         -- ^ Result consumer.
        -> IO ()
forEach :: Connection -> Query -> q -> (r -> IO ()) -> IO ()
forEach = RowParser r -> Connection -> Query -> q -> (r -> IO ()) -> IO ()
forall q r.
ToRow q =>
RowParser r -> Connection -> Query -> q -> (r -> IO ()) -> IO ()
forEachWith RowParser r
forall a. FromRow a => RowParser a
fromRow
{-# INLINE forEach #-}

-- | A version of 'forEach' taking a parser as an argument
forEachWith :: ( ToRow q )
            => RowParser r
            -> Connection
            -> Query
            -> q
            -> (r -> IO ())
            -> IO ()
forEachWith :: RowParser r -> Connection -> Query -> q -> (r -> IO ()) -> IO ()
forEachWith RowParser r
parser Connection
conn Query
template q
qs = RowParser r
-> Connection -> Query -> q -> () -> (() -> r -> IO ()) -> IO ()
forall params row a.
ToRow params =>
RowParser row
-> Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
foldWith RowParser r
parser Connection
conn Query
template q
qs () ((() -> r -> IO ()) -> IO ())
-> ((r -> IO ()) -> () -> r -> IO ()) -> (r -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> IO ()) -> () -> r -> IO ()
forall a b. a -> b -> a
const
{-# INLINE forEachWith #-}

-- | A version of 'forEach' that does not perform query substitution.
forEach_ :: (FromRow r) =>
            Connection
         -> Query                -- ^ Query template.
         -> (r -> IO ())         -- ^ Result consumer.
         -> IO ()
forEach_ :: Connection -> Query -> (r -> IO ()) -> IO ()
forEach_ = RowParser r -> Connection -> Query -> (r -> IO ()) -> IO ()
forall r.
RowParser r -> Connection -> Query -> (r -> IO ()) -> IO ()
forEachWith_ RowParser r
forall a. FromRow a => RowParser a
fromRow
{-# INLINE forEach_ #-}

forEachWith_ :: RowParser r
             -> Connection
             -> Query
             -> (r -> IO ())
             -> IO ()
forEachWith_ :: RowParser r -> Connection -> Query -> (r -> IO ()) -> IO ()
forEachWith_ RowParser r
parser Connection
conn Query
template = RowParser r
-> Connection -> Query -> () -> (() -> r -> IO ()) -> IO ()
forall r a.
RowParser r -> Connection -> Query -> a -> (a -> r -> IO a) -> IO a
foldWith_ RowParser r
parser Connection
conn Query
template () ((() -> r -> IO ()) -> IO ())
-> ((r -> IO ()) -> () -> r -> IO ()) -> (r -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> IO ()) -> () -> r -> IO ()
forall a b. a -> b -> a
const
{-# INLINE forEachWith_ #-}


-- $use
--
-- SQL-based applications are somewhat notorious for their
-- susceptibility to attacks through the injection of maliciously
-- crafted data. The primary reason for widespread vulnerability to
-- SQL injections is that many applications are sloppy in handling
-- user data when constructing SQL queries.
--
-- This library provides a 'Query' type and a parameter substitution
-- facility to address both ease of use and security.

-- $querytype
--
-- A 'Query' is a @newtype@-wrapped 'ByteString'. It intentionally
-- exposes a tiny API that is not compatible with the 'ByteString'
-- API; this makes it difficult to construct queries from fragments of
-- strings.  The 'query' and 'execute' functions require queries to be
-- of type 'Query'.
--
-- To most easily construct a query, enable GHC's @OverloadedStrings@
-- language extension and write your query as a normal literal string.
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- >
-- > import Database.PostgreSQL.Simple
-- >
-- > hello :: IO Int
-- > hello = do
-- >   conn <- connectPostgreSQL ""
-- >   [Only i] <- query_ conn "select 2 + 2"
-- >   return i
--
-- A 'Query' value does not represent the actual query that will be
-- executed, but is a template for constructing the final query.

-- $subst
--
-- Since applications need to be able to construct queries with
-- parameters that change, this library provides a query substitution
-- capability.
--
-- The 'Query' template accepted by 'query' and 'execute' can contain
-- any number of \"@?@\" characters.  Both 'query' and 'execute'
-- accept a third argument, typically a tuple. When constructing the
-- real query to execute, these functions replace the first \"@?@\" in
-- the template with the first element of the tuple, the second
-- \"@?@\" with the second element, and so on. If necessary, each
-- tuple element will be quoted and escaped prior to substitution;
-- this defeats the single most common injection vector for malicious
-- data.
--
-- For example, given the following 'Query' template:
--
-- > select * from user where first_name = ? and age > ?
--
-- And a tuple of this form:
--
-- > ("Boris" :: String, 37 :: Int)
--
-- The query to be executed will look like this after substitution:
--
-- > select * from user where first_name = 'Boris' and age > 37
--
-- If there is a mismatch between the number of \"@?@\" characters in
-- your template and the number of elements in your tuple, a
-- 'FormatError' will be thrown.
--
-- Note that the substitution functions do not attempt to parse or
-- validate your query. It's up to you to write syntactically valid
-- SQL, and to ensure that each \"@?@\" in your query template is
-- matched with the right tuple element.

-- $inference
--
-- Automated type inference means that you will often be able to avoid
-- supplying explicit type signatures for the elements of a tuple.
-- However, sometimes the compiler will not be able to infer your
-- types. Consider a case where you write a numeric literal in a
-- parameter tuple:
--
-- > query conn "select ? + ?" (40,2)
--
-- The above query will be rejected by the compiler, because it does
-- not know the specific numeric types of the literals @40@ and @2@.
-- This is easily fixed:
--
-- > query conn "select ? + ?" (40 :: Double, 2 :: Double)
--
-- The same kind of problem can arise with string literals if you have
-- the @OverloadedStrings@ language extension enabled.  Again, just
-- use an explicit type signature if this happens.
--
-- Finally, remember that the compiler must be able to infer the type
-- of a query's /results/ as well as its parameters.  We might like
-- the following example to work:
--
-- > print =<< query_ conn "select 2 + 2"
--
-- Unfortunately, while a quick glance tells us that the result type
-- should be a single row containing a single numeric column, the
-- compiler has no way to infer what the types are.  We can easily fix
-- this by providing an explicit type annotation:
--
-- > xs <- query_ conn "select 2 + 2"
-- > print (xs :: [Only Int])

-- $only_param
--
-- Haskell lacks a single-element tuple type, so if you have just one
-- value you want substituted into a query or a single-column result,
-- what should you do?
--
-- The obvious approach would appear to be something like this:
--
-- > instance (ToField a) => ToRow a where
-- >     ...
--
-- Unfortunately, this wreaks havoc with type inference, so we take a
-- different tack. To represent a single value @val@ as a parameter, write
-- a singleton list @[val]@, use 'Just' @val@, or use 'Only' @val@.
--
-- Here's an example using a singleton list:
--
-- > execute conn "insert into users (first_name) values (?)"
-- >              ["Nuala"]
--
-- A row of /n/ query results is represented using an /n/-tuple, so
-- you should use 'Only' to represent a single-column result.

-- $in
--
-- Suppose you want to write a query using an @IN@ clause:
--
-- > select * from users where first_name in ('Anna', 'Boris', 'Carla')
--
-- In such cases, it's common for both the elements and length of the
-- list after the @IN@ keyword to vary from query to query.
--
-- To address this case, use the 'In' type wrapper, and use a single
-- \"@?@\" character to represent the list.  Omit the parentheses
-- around the list; these will be added for you.
--
-- Here's an example:
--
-- > query conn "select * from users where first_name in ?" $
-- >       Only $ In ["Anna", "Boris", "Carla"]
--
-- If your 'In'-wrapped list is empty, the string @\"(null)\"@ will be
-- substituted instead, to ensure that your clause remains
-- syntactically valid.

-- $many
--
-- If you know that you have many rows of data to insert into a table,
-- it is much more efficient to perform all the insertions in a single
-- multi-row @INSERT@ statement than individually.
--
-- The 'executeMany' function is intended specifically for helping
-- with multi-row @INSERT@ and @UPDATE@ statements. Its rules for
-- query substitution are different than those for 'execute'.
--
-- What 'executeMany' searches for in your 'Query' template is a
-- single substring of the form:
--
-- > values (?,?,?)
--
-- The rules are as follows:
--
-- * The keyword @VALUES@ is matched case insensitively.
--
-- * There must be no other \"@?@\" characters anywhere in your
--   template.
--
-- * There must be one or more \"@?@\" in the parentheses.
--
-- * Extra white space is fine.
--
-- The last argument to 'executeMany' is a list of parameter
-- tuples. These will be substituted into the query where the @(?,?)@
-- string appears, in a form suitable for use in a multi-row @INSERT@
-- or @UPDATE@.
--
-- Here is an example:
--
-- > executeMany conn
-- >   "insert into users (first_name,last_name) values (?,?)"
-- >   [("Boris","Karloff"),("Ed","Wood")]
--
-- The query that will be executed here will look like this
-- (reformatted for tidiness):
--
-- > insert into users (first_name,last_name) values
-- >   ('Boris','Karloff'),('Ed','Wood')

-- $returning
--
-- PostgreSQL supports returning values from data manipulation statements
-- such as @INSERT@ and @UPDATE@.   You can use these statements by
-- using 'query' instead of 'execute'.   For multi-tuple inserts,
-- use 'returning' instead of 'executeMany'.
--
-- For example, were there an auto-incrementing @id@ column and
-- timestamp column @t@ that defaulted to the present time for the
-- @sales@ table, then the following query would insert two new
-- sales records and also return their new @id@s and timestamps.
--
-- > let q = "insert into sales (amount, label) values (?,?) returning id, t"
-- > xs :: [(Int, UTCTime)] <- query conn q (15,"Sawdust")
-- > ys :: [(Int, UTCTime)] <- returning conn q [(20,"Chips"),(300,"Wood")]

-- $result
--
-- The 'query' and 'query_' functions return a list of values in the
-- 'FromRow' typeclass. This class performs automatic extraction
-- and type conversion of rows from a query result.
--
-- Here is a simple example of how to extract results:
--
-- > import qualified Data.Text as Text
-- >
-- > xs <- query_ conn "select name,age from users"
-- > forM_ xs $ \(name,age) ->
-- >   putStrLn $ Text.unpack name ++ " is " ++ show (age :: Int)
--
-- Notice two important details about this code:
--
-- * The number of columns we ask for in the query template must
--   exactly match the number of elements we specify in a row of the
--   result tuple.  If they do not match, a 'ResultError' exception
--   will be thrown.
--
-- * Sometimes, the compiler needs our help in specifying types. It
--   can infer that @name@ must be a 'Text', due to our use of the
--   @unpack@ function. However, we have to tell it the type of @age@,
--   as it has no other information to determine the exact type.

-- $null
--
-- The type of a result tuple will look something like this:
--
-- > (Text, Int, Int)
--
-- Although SQL can accommodate @NULL@ as a value for any of these
-- types, Haskell cannot. If your result contains columns that may be
-- @NULL@, be sure that you use 'Maybe' in those positions of your
-- tuple.
--
-- > (Text, Maybe Int, Int)
--
-- If 'query' encounters a @NULL@ in a row where the corresponding
-- Haskell type is not 'Maybe', it will throw a 'ResultError'
-- exception.

-- $only_result
--
-- To specify that a query returns a single-column result, use the
-- 'Only' type.
--
-- > xs <- query_ conn "select id from users"
-- > forM_ xs $ \(Only dbid) -> {- ... -}

-- $types
--
-- Conversion of SQL values to Haskell values is somewhat
-- permissive. Here are the rules.
--
-- * For numeric types, any Haskell type that can accurately represent
--   all values of the given PostgreSQL type is considered \"compatible\".
--   For instance, you can always extract a PostgreSQL 16-bit @SMALLINT@
--   column to a Haskell 'Int'.  The Haskell 'Float' type can accurately
--   represent a @SMALLINT@, so it is considered compatble with those types.
--
-- * A numeric compatibility check is based only on the type of a
--   column, /not/ on its values. For instance, a PostgreSQL 64-bit
--   @BIGINT@ column will be considered incompatible with a Haskell
--   'Int16', even if it contains the value @1@.
--
-- * If a numeric incompatibility is found, 'query' will throw a
--   'ResultError'.
--
-- * The 'String' and 'Text' types are assumed to be encoded as
--   UTF-8. If you use some other encoding, decoding may fail or give
--   wrong results. In such cases, write a @newtype@ wrapper and a
--   custom 'Result' instance to handle your encoding.