{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
module Database.PostgreSQL.Simple
    (
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
      Connection
    , Query
    , ToRow
    , FromRow
    , In(..)
    , Binary(..)
    , Only(..)
    , (:.)(..)
    
    , SqlError(..)
    , PQ.ExecStatus(..)
    , FormatError(..)
    , QueryError(..)
    , ResultError(..)
    
    , Base.connectPostgreSQL
    , Base.close
    , Base.connect
    , Base.ConnectInfo(..)
    , Base.defaultConnectInfo
    , Base.postgreSQLConnectionString
    
    , query
    , query_
    
    , queryWith
    , queryWith_
    
    , FoldOptions(..)
    , FetchQuantity(..)
    , defaultFoldOptions
    , fold
    , foldWithOptions
    , fold_
    , foldWithOptions_
    , forEach
    , forEach_
    , returning
    
    , foldWith
    , foldWithOptionsAndParser
    , foldWith_
    , foldWithOptionsAndParser_
    , forEachWith
    , forEachWith_
    , returningWith
    
    , execute
    , execute_
    , executeMany
    
    , withTransaction
    , withSavepoint
    , begin
    , commit
    , rollback
    
    , 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
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
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 []
parseTemplate :: ByteString -> Maybe (ByteString, ByteString, ByteString)
parseTemplate :: ByteString -> Maybe (ByteString, ByteString, ByteString)
parseTemplate ByteString
template =
    
    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 :: ByteString -> Maybe (ByteString, ByteString, ByteString)
search ByteString
bs =
        case ByteString -> ByteString -> (ByteString, ByteString)
B.breakSubstring ByteString
"VALUES" ByteString
bs of
            (ByteString
x, ByteString
y)
                
                
                | 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
                
                
                | 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
                
                | 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
    
    
    
    
    
    
    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
    
    
    
    
    
    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
    
    
    
    
    
    
    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
    
    
    
    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
'$'
    
    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 =
            
            
            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 :: (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
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
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
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
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
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
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
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
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
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
data FetchQuantity
   = Automatic
   | Fixed !Int
data FoldOptions
   = FoldOptions {
       FoldOptions -> FetchQuantity
fetchQuantity   :: !FetchQuantity,
       FoldOptions -> TransactionMode
transactionMode :: !TransactionMode
     }
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
    }
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
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
fold_ :: (FromRow r) =>
         Connection
      -> Query                  
      -> a                      
      -> (a -> r -> IO a)       
      -> 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
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             
                 -> a                 
                 -> (a -> r -> IO a)  
                 -> 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
foldWithOptionsAndParser_ :: FoldOptions
                          -> RowParser r
                          -> Connection
                          -> Query             
                          -> a                 
                          -> (a -> r -> IO a)  
                          -> 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"
         
         
         
         
         
      TransactionStatus
PQ.TransInError -> String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"foldWithOpts FIXME:  PQ.TransInError"
         
         
         
      TransactionStatus
PQ.TransUnknown -> String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"foldWithOpts FIXME:  PQ.TransUnknown"
         
  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
    chunkSize :: Int
chunkSize = case FetchQuantity
fetchQuantity of
                 FetchQuantity
Automatic   -> Int
256
                 Fixed Int
n     -> Int
n
forEach :: (ToRow q, FromRow r) =>
           Connection
        -> Query                
        -> q                    
        -> (r -> IO ())         
        -> 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 #-}
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 #-}
forEach_ :: (FromRow r) =>
            Connection
         -> Query                
         -> (r -> IO ())         
         -> 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_ #-}