{-# LINE 1 "src/Database/PostgreSQL/LibPQ.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Database.PostgreSQL.LibPQ
(
Connection
, connectdb
, connectStart
, connectPoll
, newNullConnection
, isNullConnection
, reset
, resetStart
, resetPoll
, PollingStatus(..)
, finish
, db
, user
, pass
, host
, port
, options
, ConnStatus(..)
, status
, TransactionStatus(..)
, transactionStatus
, parameterStatus
, protocolVersion
, serverVersion
, libpqVersion
, errorMessage
, socket
, backendPID
, connectionNeedsPassword
, connectionUsedPassword
, Result
, exec
, Format(..)
, Oid(..)
, invalidOid
, execParams
, prepare
, execPrepared
, describePrepared
, describePortal
, ExecStatus(..)
, resultStatus
, resStatus
, resultErrorMessage
, FieldCode(..)
, resultErrorField
, unsafeFreeResult
, ntuples
, nfields
, Row(..)
, Column(..)
, toRow
, toColumn
, fname
, fnumber
, ftable
, ftablecol
, fformat
, ftype
, fmod
, fsize
, getvalue
, getvalue'
, getisnull
, getlength
, nparams
, paramtype
, cmdStatus
, cmdTuples
, escapeStringConn
, escapeByteaConn
, unescapeBytea
, escapeIdentifier
, CopyInResult(..)
, putCopyData
, putCopyEnd
, CopyOutResult(..)
, getCopyData
, sendQuery
, sendQueryParams
, sendPrepare
, sendQueryPrepared
, sendDescribePrepared
, sendDescribePortal
, getResult
, consumeInput
, isBusy
, setnonblocking
, isnonblocking
, setSingleRowMode
, FlushStatus(..)
, flush
, Cancel
, getCancel
, cancel
, Notify(..)
, notifies
, clientEncoding
, setClientEncoding
, Verbosity(..)
, setErrorVerbosity
, disableNoticeReporting
, enableNoticeReporting
, getNotice
, LoFd(..)
, loCreat
, loCreate
, loImport
, loImportWithOid
, loExport
, loOpen
, loWrite
, loRead
, loSeek
, loTell
, loTruncate
, loClose
, loUnlink
)
where
import Prelude hiding ( print )
import Foreign
import Foreign.C.Types
import Foreign.C.String
{-# LINE 224 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import qualified Foreign.ForeignPtr.Unsafe as Unsafe
{-# LINE 226 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import qualified Foreign.Concurrent as FC
import System.Posix.Types ( Fd(..) )
import Data.List ( foldl' )
import System.IO ( IOMode(..), SeekMode(..) )
{-# LINE 232 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import GHC.Conc ( closeFdWith )
{-# LINE 234 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import System.Posix.Types ( CPid )
import Data.ByteString.Char8 ()
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Internal as B ( fromForeignPtr
, c_strlen
, createAndTrim
)
import qualified Data.ByteString as B
import Control.Concurrent.MVar
import Data.Typeable
import Database.PostgreSQL.LibPQ.Compat
import Database.PostgreSQL.LibPQ.Internal
{-# LINE 252 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import Control.Exception (mask_)
{-# LINE 257 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import Control.Exception (try, IOException)
{-# LINE 261 "src/Database/PostgreSQL/LibPQ.hsc" #-}
import System.Posix.DynamicLinker
{-# LINE 265 "src/Database/PostgreSQL/LibPQ.hsc" #-}
connectdb :: B.ByteString
-> IO Connection
connectdb :: ByteString -> IO Connection
connectdb ByteString
conninfo =
IO Connection -> IO Connection
forall a. IO a -> IO a
mask_ (IO Connection -> IO Connection) -> IO Connection -> IO Connection
forall a b. (a -> b) -> a -> b
$ do
Ptr PGconn
connPtr <- ByteString -> (CString -> IO (Ptr PGconn)) -> IO (Ptr PGconn)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
conninfo CString -> IO (Ptr PGconn)
c_PQconnectdb
if Ptr PGconn
connPtr Ptr PGconn -> Ptr PGconn -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGconn
forall a. Ptr a
nullPtr
then String -> IO Connection
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"libpq failed to allocate a PGconn structure"
else do
MVar (Ptr CNoticeBuffer)
noticeBuffer <- Ptr CNoticeBuffer -> IO (MVar (Ptr CNoticeBuffer))
forall a. a -> IO (MVar a)
newMVar Ptr CNoticeBuffer
forall a. Ptr a
nullPtr
ForeignPtr PGconn
connection <- Ptr PGconn -> IO () -> IO (ForeignPtr PGconn)
forall a. Ptr a -> IO () -> IO (ForeignPtr a)
newForeignPtrOnce Ptr PGconn
connPtr (Ptr PGconn -> MVar (Ptr CNoticeBuffer) -> IO ()
pqfinish Ptr PGconn
connPtr MVar (Ptr CNoticeBuffer)
noticeBuffer)
Connection -> IO Connection
forall (m :: * -> *) a. Monad m => a -> m a
return (Connection -> IO Connection) -> Connection -> IO Connection
forall a b. (a -> b) -> a -> b
$! ForeignPtr PGconn -> MVar (Ptr CNoticeBuffer) -> Connection
Conn ForeignPtr PGconn
connection MVar (Ptr CNoticeBuffer)
noticeBuffer
connectStart :: B.ByteString
-> IO Connection
connectStart :: ByteString -> IO Connection
connectStart ByteString
connStr =
IO Connection -> IO Connection
forall a. IO a -> IO a
mask_ (IO Connection -> IO Connection) -> IO Connection -> IO Connection
forall a b. (a -> b) -> a -> b
$ do
Ptr PGconn
connPtr <- ByteString -> (CString -> IO (Ptr PGconn)) -> IO (Ptr PGconn)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
connStr CString -> IO (Ptr PGconn)
c_PQconnectStart
if Ptr PGconn
connPtr Ptr PGconn -> Ptr PGconn -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGconn
forall a. Ptr a
nullPtr
then String -> IO Connection
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"libpq failed to allocate a PGconn structure"
else do
MVar (Ptr CNoticeBuffer)
noticeBuffer <- Ptr CNoticeBuffer -> IO (MVar (Ptr CNoticeBuffer))
forall a. a -> IO (MVar a)
newMVar Ptr CNoticeBuffer
forall a. Ptr a
nullPtr
ForeignPtr PGconn
connection <- Ptr PGconn -> IO () -> IO (ForeignPtr PGconn)
forall a. Ptr a -> IO () -> IO (ForeignPtr a)
newForeignPtrOnce Ptr PGconn
connPtr (Ptr PGconn -> MVar (Ptr CNoticeBuffer) -> IO ()
pqfinish Ptr PGconn
connPtr MVar (Ptr CNoticeBuffer)
noticeBuffer)
Connection -> IO Connection
forall (m :: * -> *) a. Monad m => a -> m a
return (Connection -> IO Connection) -> Connection -> IO Connection
forall a b. (a -> b) -> a -> b
$! ForeignPtr PGconn -> MVar (Ptr CNoticeBuffer) -> Connection
Conn ForeignPtr PGconn
connection MVar (Ptr CNoticeBuffer)
noticeBuffer
pqfinish :: Ptr PGconn -> MVar NoticeBuffer -> IO ()
pqfinish :: Ptr PGconn -> MVar (Ptr CNoticeBuffer) -> IO ()
pqfinish Ptr PGconn
conn MVar (Ptr CNoticeBuffer)
noticeBuffer = do
{-# LINE 317 "src/Database/PostgreSQL/LibPQ.hsc" #-}
CInt
mfd <- Ptr PGconn -> IO CInt
c_PQsocket Ptr PGconn
conn
case CInt
mfd of
-1 ->
Ptr PGconn -> IO ()
c_PQfinish Ptr PGconn
conn
CInt
fd -> (Fd -> IO ()) -> Fd -> IO ()
closeFdWith (\Fd
_ -> Ptr PGconn -> IO ()
c_PQfinish Ptr PGconn
conn) (CInt -> Fd
Fd CInt
fd)
{-# LINE 332 "src/Database/PostgreSQL/LibPQ.hsc" #-}
Ptr CNoticeBuffer
nb <- MVar (Ptr CNoticeBuffer)
-> Ptr CNoticeBuffer -> IO (Ptr CNoticeBuffer)
forall a. MVar a -> a -> IO a
swapMVar MVar (Ptr CNoticeBuffer)
noticeBuffer Ptr CNoticeBuffer
forall a. Ptr a
nullPtr
Ptr CNoticeBuffer -> IO ()
c_free_noticebuffer Ptr CNoticeBuffer
nb
newForeignPtrOnce :: Ptr a -> IO () -> IO (ForeignPtr a)
newForeignPtrOnce :: Ptr a -> IO () -> IO (ForeignPtr a)
newForeignPtrOnce Ptr a
ptr IO ()
fin = do
MVar (IO ())
mv <- IO () -> IO (MVar (IO ()))
forall a. a -> IO (MVar a)
newMVar IO ()
fin
Ptr a -> IO () -> IO (ForeignPtr a)
forall a. Ptr a -> IO () -> IO (ForeignPtr a)
FC.newForeignPtr Ptr a
ptr (IO () -> IO (ForeignPtr a)) -> IO () -> IO (ForeignPtr a)
forall a b. (a -> b) -> a -> b
$ MVar (IO ()) -> IO (Maybe (IO ()))
forall a. MVar a -> IO (Maybe a)
tryTakeMVar MVar (IO ())
mv IO (Maybe (IO ())) -> (Maybe (IO ()) -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> (IO () -> IO ()) -> Maybe (IO ()) -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) IO () -> IO ()
forall a. a -> a
id
newNullConnection :: IO Connection
newNullConnection :: IO Connection
newNullConnection = do
ForeignPtr PGconn
connection <- Ptr PGconn -> IO (ForeignPtr PGconn)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ Ptr PGconn
forall a. Ptr a
nullPtr
MVar (Ptr CNoticeBuffer)
noticeBuffer <- Ptr CNoticeBuffer -> IO (MVar (Ptr CNoticeBuffer))
forall a. a -> IO (MVar a)
newMVar Ptr CNoticeBuffer
forall a. Ptr a
nullPtr
Connection -> IO Connection
forall (m :: * -> *) a. Monad m => a -> m a
return (Connection -> IO Connection) -> Connection -> IO Connection
forall a b. (a -> b) -> a -> b
$! ForeignPtr PGconn -> MVar (Ptr CNoticeBuffer) -> Connection
Conn ForeignPtr PGconn
connection MVar (Ptr CNoticeBuffer)
noticeBuffer
isNullConnection :: Connection -> Bool
{-# LINE 356 "src/Database/PostgreSQL/LibPQ.hsc" #-}
isNullConnection (Conn x _) = Unsafe.unsafeForeignPtrToPtr x == nullPtr
{-# LINE 360 "src/Database/PostgreSQL/LibPQ.hsc" #-}
{-# INLINE isNullConnection #-}
connectPoll :: Connection
-> IO PollingStatus
connectPoll :: Connection -> IO PollingStatus
connectPoll = (Ptr PGconn -> IO CInt) -> Connection -> IO PollingStatus
pollHelper Ptr PGconn -> IO CInt
c_PQconnectPoll
reset :: Connection
-> IO ()
reset :: Connection -> IO ()
reset Connection
connection = Connection -> (Ptr PGconn -> IO ()) -> IO ()
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO ()
c_PQreset
resetStart :: Connection
-> IO Bool
resetStart :: Connection -> IO Bool
resetStart Connection
connection =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQresetStart
resetPoll :: Connection
-> IO PollingStatus
resetPoll :: Connection -> IO PollingStatus
resetPoll = (Ptr PGconn -> IO CInt) -> Connection -> IO PollingStatus
pollHelper Ptr PGconn -> IO CInt
c_PQresetPoll
data PollingStatus
= PollingFailed
| PollingReading
| PollingWriting
| PollingOk deriving (PollingStatus -> PollingStatus -> Bool
(PollingStatus -> PollingStatus -> Bool)
-> (PollingStatus -> PollingStatus -> Bool) -> Eq PollingStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollingStatus -> PollingStatus -> Bool
$c/= :: PollingStatus -> PollingStatus -> Bool
== :: PollingStatus -> PollingStatus -> Bool
$c== :: PollingStatus -> PollingStatus -> Bool
Eq, Int -> PollingStatus -> ShowS
[PollingStatus] -> ShowS
PollingStatus -> String
(Int -> PollingStatus -> ShowS)
-> (PollingStatus -> String)
-> ([PollingStatus] -> ShowS)
-> Show PollingStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollingStatus] -> ShowS
$cshowList :: [PollingStatus] -> ShowS
show :: PollingStatus -> String
$cshow :: PollingStatus -> String
showsPrec :: Int -> PollingStatus -> ShowS
$cshowsPrec :: Int -> PollingStatus -> ShowS
Show)
pollHelper :: (Ptr PGconn -> IO CInt)
-> Connection
-> IO PollingStatus
pollHelper :: (Ptr PGconn -> IO CInt) -> Connection -> IO PollingStatus
pollHelper Ptr PGconn -> IO CInt
poller Connection
connection =
do CInt
code <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
poller
case CInt
code of
(CInt
1) -> PollingStatus -> IO PollingStatus
forall (m :: * -> *) a. Monad m => a -> m a
return PollingStatus
PollingReading
{-# LINE 456 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(CInt
3) -> PollingStatus -> IO PollingStatus
forall (m :: * -> *) a. Monad m => a -> m a
return PollingStatus
PollingOk
{-# LINE 457 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(CInt
2) -> PollingStatus -> IO PollingStatus
forall (m :: * -> *) a. Monad m => a -> m a
return PollingStatus
PollingWriting
{-# LINE 458 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(CInt
0) -> PollingStatus -> IO PollingStatus
forall (m :: * -> *) a. Monad m => a -> m a
return PollingStatus
PollingFailed
{-# LINE 459 "src/Database/PostgreSQL/LibPQ.hsc" #-}
CInt
_ -> String -> IO PollingStatus
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO PollingStatus) -> String -> IO PollingStatus
forall a b. (a -> b) -> a -> b
$ String
"unexpected polling status " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CInt -> String
forall a. Show a => a -> String
show CInt
code
finish :: Connection
-> IO ()
finish :: Connection -> IO ()
finish (Conn ForeignPtr PGconn
fp MVar (Ptr CNoticeBuffer)
_) =
do ForeignPtr PGconn -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr ForeignPtr PGconn
fp
db :: Connection
-> IO (Maybe B.ByteString)
db :: Connection -> IO (Maybe ByteString)
db = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQdb
user :: Connection
-> IO (Maybe B.ByteString)
user :: Connection -> IO (Maybe ByteString)
user = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQuser
pass :: Connection
-> IO (Maybe B.ByteString)
pass :: Connection -> IO (Maybe ByteString)
pass = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQpass
host :: Connection
-> IO (Maybe B.ByteString)
host :: Connection -> IO (Maybe ByteString)
host = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQhost
port :: Connection
-> IO (Maybe B.ByteString)
port :: Connection -> IO (Maybe ByteString)
port = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQport
options :: Connection
-> IO (Maybe B.ByteString)
options :: Connection -> IO (Maybe ByteString)
options = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQoptions
statusString :: (Ptr PGconn -> IO CString)
-> Connection
-> IO (Maybe B.ByteString)
statusString :: (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
f Connection
connection =
Connection
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr ->
do CString
cstr <- Ptr PGconn -> IO CString
f Ptr PGconn
ptr
if CString
cstr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CString -> IO ByteString
B.packCString CString
cstr
data ConnStatus
= ConnectionOk
| ConnectionBad
| ConnectionStarted
| ConnectionMade
| ConnectionAwaitingResponse
| ConnectionAuthOk
| ConnectionSetEnv
| ConnectionSSLStartup
deriving (ConnStatus -> ConnStatus -> Bool
(ConnStatus -> ConnStatus -> Bool)
-> (ConnStatus -> ConnStatus -> Bool) -> Eq ConnStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnStatus -> ConnStatus -> Bool
$c/= :: ConnStatus -> ConnStatus -> Bool
== :: ConnStatus -> ConnStatus -> Bool
$c== :: ConnStatus -> ConnStatus -> Bool
Eq, Int -> ConnStatus -> ShowS
[ConnStatus] -> ShowS
ConnStatus -> String
(Int -> ConnStatus -> ShowS)
-> (ConnStatus -> String)
-> ([ConnStatus] -> ShowS)
-> Show ConnStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnStatus] -> ShowS
$cshowList :: [ConnStatus] -> ShowS
show :: ConnStatus -> String
$cshow :: ConnStatus -> String
showsPrec :: Int -> ConnStatus -> ShowS
$cshowsPrec :: Int -> ConnStatus -> ShowS
Show)
status :: Connection
-> IO ConnStatus
status :: Connection -> IO ConnStatus
status Connection
connection = do
CInt
stat <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQstatus
case CInt
stat of
(CInt
0) -> ConnStatus -> IO ConnStatus
forall (m :: * -> *) a. Monad m => a -> m a
return ConnStatus
ConnectionOk
{-# LINE 560 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(1) -> return ConnectionBad
{-# LINE 561 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(2) -> return ConnectionStarted
{-# LINE 562 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(3) -> return ConnectionMade
{-# LINE 563 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(4)-> return ConnectionAwaitingResponse
{-# LINE 564 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(5) -> return ConnectionAuthOk
{-# LINE 565 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(6) -> return ConnectionSetEnv
{-# LINE 566 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(7) -> return ConnectionSSLStartup
{-# LINE 567 "src/Database/PostgreSQL/LibPQ.hsc" #-}
CInt
c -> String -> IO ConnStatus
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ConnStatus) -> String -> IO ConnStatus
forall a b. (a -> b) -> a -> b
$ String
"Unknown connection status " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CInt -> String
forall a. Show a => a -> String
show CInt
c
data TransactionStatus = TransIdle
| TransActive
| TransInTrans
| TransInError
| TransUnknown
deriving (TransactionStatus -> TransactionStatus -> Bool
(TransactionStatus -> TransactionStatus -> Bool)
-> (TransactionStatus -> TransactionStatus -> Bool)
-> Eq TransactionStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionStatus -> TransactionStatus -> Bool
$c/= :: TransactionStatus -> TransactionStatus -> Bool
== :: TransactionStatus -> TransactionStatus -> Bool
$c== :: TransactionStatus -> TransactionStatus -> Bool
Eq, Int -> TransactionStatus -> ShowS
[TransactionStatus] -> ShowS
TransactionStatus -> String
(Int -> TransactionStatus -> ShowS)
-> (TransactionStatus -> String)
-> ([TransactionStatus] -> ShowS)
-> Show TransactionStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionStatus] -> ShowS
$cshowList :: [TransactionStatus] -> ShowS
show :: TransactionStatus -> String
$cshow :: TransactionStatus -> String
showsPrec :: Int -> TransactionStatus -> ShowS
$cshowsPrec :: Int -> TransactionStatus -> ShowS
Show)
transactionStatus :: Connection
-> IO TransactionStatus
transactionStatus :: Connection -> IO TransactionStatus
transactionStatus Connection
connection = do
CInt
stat <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQtransactionStatus
case CInt
stat of
(CInt
0) -> TransactionStatus -> IO TransactionStatus
forall (m :: * -> *) a. Monad m => a -> m a
return TransactionStatus
TransIdle
{-# LINE 588 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(1) -> return TransActive
{-# LINE 589 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(2) -> return TransInTrans
{-# LINE 590 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(3) -> return TransInError
{-# LINE 591 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(4) -> return TransUnknown
{-# LINE 592 "src/Database/PostgreSQL/LibPQ.hsc" #-}
c -> fail $ "Unknown transaction status " ++ show c
parameterStatus :: Connection
-> B.ByteString
-> IO (Maybe B.ByteString)
parameterStatus :: Connection -> ByteString -> IO (Maybe ByteString)
parameterStatus Connection
connection ByteString
paramName =
Connection
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
connPtr ->
ByteString
-> (CString -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
paramName ((CString -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (CString -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \CString
paramNamePtr ->
do CString
cstr <- Ptr PGconn -> CString -> IO CString
c_PQparameterStatus Ptr PGconn
connPtr CString
paramNamePtr
if CString
cstr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CString -> IO ByteString
B.packCString CString
cstr
protocolVersion :: Connection
-> IO Int
protocolVersion :: Connection -> IO Int
protocolVersion Connection
connection =
(CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CInt -> IO Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> a -> b
$ Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQprotocolVersion
serverVersion :: Connection
-> IO Int
serverVersion :: Connection -> IO Int
serverVersion Connection
connection =
(CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CInt -> IO Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> a -> b
$ Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQserverVersion
libpqVersion :: IO Int
libpqVersion :: IO Int
libpqVersion = do
{-# LINE 658 "src/Database/PostgreSQL/LibPQ.hsc" #-}
res <- try (dlsym Default "PQlibVersion") :: IO (Either IOException (FunPtr Int))
{-# LINE 663 "src/Database/PostgreSQL/LibPQ.hsc" #-}
case res of
Left _ -> error "libpqVersion is not supported for libpq < 9.1"
Right funPtr -> return $ mkLibpqVersion funPtr
errorMessage :: Connection
-> IO (Maybe B.ByteString)
errorMessage :: Connection -> IO (Maybe ByteString)
errorMessage = (Ptr PGconn -> IO CString) -> Connection -> IO (Maybe ByteString)
statusString Ptr PGconn -> IO CString
c_PQerrorMessage
socket :: Connection
-> IO (Maybe Fd)
socket :: Connection -> IO (Maybe Fd)
socket Connection
connection =
do CInt
cFd <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQsocket
case CInt
cFd of
-1 -> Maybe Fd -> IO (Maybe Fd)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Fd
forall a. Maybe a
Nothing
CInt
_ -> Maybe Fd -> IO (Maybe Fd)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Fd -> IO (Maybe Fd)) -> Maybe Fd -> IO (Maybe Fd)
forall a b. (a -> b) -> a -> b
$ Fd -> Maybe Fd
forall a. a -> Maybe a
Just (Fd -> Maybe Fd) -> Fd -> Maybe Fd
forall a b. (a -> b) -> a -> b
$ CInt -> Fd
Fd CInt
cFd
backendPID :: Connection
-> IO CPid
backendPID :: Connection -> IO CPid
backendPID Connection
connection =
(CInt -> CPid) -> IO CInt -> IO CPid
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> CPid
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CInt -> IO CPid) -> IO CInt -> IO CPid
forall a b. (a -> b) -> a -> b
$ Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQbackendPID
connectionNeedsPassword :: Connection
-> IO Bool
connectionNeedsPassword :: Connection -> IO Bool
connectionNeedsPassword Connection
connection =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQconnectionNeedsPassword
connectionUsedPassword :: Connection
-> IO Bool
connectionUsedPassword :: Connection -> IO Bool
connectionUsedPassword Connection
connection =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQconnectionUsedPassword
newtype Result = Result (ForeignPtr PGresult) deriving (Result -> Result -> Bool
(Result -> Result -> Bool)
-> (Result -> Result -> Bool) -> Eq Result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
Eq, Int -> Result -> ShowS
[Result] -> ShowS
Result -> String
(Int -> Result -> ShowS)
-> (Result -> String) -> ([Result] -> ShowS) -> Show Result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result] -> ShowS
$cshowList :: [Result] -> ShowS
show :: Result -> String
$cshow :: Result -> String
showsPrec :: Int -> Result -> ShowS
$cshowsPrec :: Int -> Result -> ShowS
Show)
data PGresult
data Format = Text | Binary deriving (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c== :: Format -> Format -> Bool
Eq, Eq Format
Eq Format
-> (Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmax :: Format -> Format -> Format
>= :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c< :: Format -> Format -> Bool
compare :: Format -> Format -> Ordering
$ccompare :: Format -> Format -> Ordering
$cp1Ord :: Eq Format
Ord, Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Format] -> ShowS
$cshowList :: [Format] -> ShowS
show :: Format -> String
$cshow :: Format -> String
showsPrec :: Int -> Format -> ShowS
$cshowsPrec :: Int -> Format -> ShowS
Show, Int -> Format
Format -> Int
Format -> [Format]
Format -> Format
Format -> Format -> [Format]
Format -> Format -> Format -> [Format]
(Format -> Format)
-> (Format -> Format)
-> (Int -> Format)
-> (Format -> Int)
-> (Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> Format -> [Format])
-> Enum Format
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Format -> Format -> Format -> [Format]
$cenumFromThenTo :: Format -> Format -> Format -> [Format]
enumFromTo :: Format -> Format -> [Format]
$cenumFromTo :: Format -> Format -> [Format]
enumFromThen :: Format -> Format -> [Format]
$cenumFromThen :: Format -> Format -> [Format]
enumFrom :: Format -> [Format]
$cenumFrom :: Format -> [Format]
fromEnum :: Format -> Int
$cfromEnum :: Format -> Int
toEnum :: Int -> Format
$ctoEnum :: Int -> Format
pred :: Format -> Format
$cpred :: Format -> Format
succ :: Format -> Format
$csucc :: Format -> Format
Enum)
newtype Oid = Oid CUInt deriving (Oid -> Oid -> Bool
(Oid -> Oid -> Bool) -> (Oid -> Oid -> Bool) -> Eq Oid
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Oid -> Oid -> Bool
$c/= :: Oid -> Oid -> Bool
== :: Oid -> Oid -> Bool
$c== :: Oid -> Oid -> Bool
Eq, Eq Oid
Eq Oid
-> (Oid -> Oid -> Ordering)
-> (Oid -> Oid -> Bool)
-> (Oid -> Oid -> Bool)
-> (Oid -> Oid -> Bool)
-> (Oid -> Oid -> Bool)
-> (Oid -> Oid -> Oid)
-> (Oid -> Oid -> Oid)
-> Ord Oid
Oid -> Oid -> Bool
Oid -> Oid -> Ordering
Oid -> Oid -> Oid
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Oid -> Oid -> Oid
$cmin :: Oid -> Oid -> Oid
max :: Oid -> Oid -> Oid
$cmax :: Oid -> Oid -> Oid
>= :: Oid -> Oid -> Bool
$c>= :: Oid -> Oid -> Bool
> :: Oid -> Oid -> Bool
$c> :: Oid -> Oid -> Bool
<= :: Oid -> Oid -> Bool
$c<= :: Oid -> Oid -> Bool
< :: Oid -> Oid -> Bool
$c< :: Oid -> Oid -> Bool
compare :: Oid -> Oid -> Ordering
$ccompare :: Oid -> Oid -> Ordering
$cp1Ord :: Eq Oid
Ord, ReadPrec [Oid]
ReadPrec Oid
Int -> ReadS Oid
ReadS [Oid]
(Int -> ReadS Oid)
-> ReadS [Oid] -> ReadPrec Oid -> ReadPrec [Oid] -> Read Oid
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Oid]
$creadListPrec :: ReadPrec [Oid]
readPrec :: ReadPrec Oid
$creadPrec :: ReadPrec Oid
readList :: ReadS [Oid]
$creadList :: ReadS [Oid]
readsPrec :: Int -> ReadS Oid
$creadsPrec :: Int -> ReadS Oid
Read, Int -> Oid -> ShowS
[Oid] -> ShowS
Oid -> String
(Int -> Oid -> ShowS)
-> (Oid -> String) -> ([Oid] -> ShowS) -> Show Oid
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Oid] -> ShowS
$cshowList :: [Oid] -> ShowS
show :: Oid -> String
$cshow :: Oid -> String
showsPrec :: Int -> Oid -> ShowS
$cshowsPrec :: Int -> Oid -> ShowS
Show, Ptr b -> Int -> IO Oid
Ptr b -> Int -> Oid -> IO ()
Ptr Oid -> IO Oid
Ptr Oid -> Int -> IO Oid
Ptr Oid -> Int -> Oid -> IO ()
Ptr Oid -> Oid -> IO ()
Oid -> Int
(Oid -> Int)
-> (Oid -> Int)
-> (Ptr Oid -> Int -> IO Oid)
-> (Ptr Oid -> Int -> Oid -> IO ())
-> (forall b. Ptr b -> Int -> IO Oid)
-> (forall b. Ptr b -> Int -> Oid -> IO ())
-> (Ptr Oid -> IO Oid)
-> (Ptr Oid -> Oid -> IO ())
-> Storable Oid
forall b. Ptr b -> Int -> IO Oid
forall b. Ptr b -> Int -> Oid -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Oid -> Oid -> IO ()
$cpoke :: Ptr Oid -> Oid -> IO ()
peek :: Ptr Oid -> IO Oid
$cpeek :: Ptr Oid -> IO Oid
pokeByteOff :: Ptr b -> Int -> Oid -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Oid -> IO ()
peekByteOff :: Ptr b -> Int -> IO Oid
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Oid
pokeElemOff :: Ptr Oid -> Int -> Oid -> IO ()
$cpokeElemOff :: Ptr Oid -> Int -> Oid -> IO ()
peekElemOff :: Ptr Oid -> Int -> IO Oid
$cpeekElemOff :: Ptr Oid -> Int -> IO Oid
alignment :: Oid -> Int
$calignment :: Oid -> Int
sizeOf :: Oid -> Int
$csizeOf :: Oid -> Int
Storable, Typeable)
invalidOid :: Oid
invalidOid :: Oid
invalidOid = CUInt -> Oid
Oid (CUInt
0)
{-# LINE 748 "src/Database/PostgreSQL/LibPQ.hsc" #-}
exec :: Connection
-> B.ByteString
-> IO (Maybe Result)
exec :: Connection -> ByteString -> IO (Maybe Result)
exec Connection
connection ByteString
query =
Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection ((Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result))
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
p ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ Ptr PGconn -> CString -> IO (Ptr PGresult)
c_PQexec Ptr PGconn
p
execParams :: Connection
-> B.ByteString
-> [Maybe (Oid, B.ByteString, Format)]
-> Format
-> IO (Maybe Result)
execParams :: Connection
-> ByteString
-> [Maybe (Oid, ByteString, Format)]
-> Format
-> IO (Maybe Result)
execParams Connection
connection ByteString
statement [Maybe (Oid, ByteString, Format)]
params Format
rFmt =
do let ([Oid]
oids, [Maybe ByteString]
values, [Int]
lengths, [CInt]
formats) =
(([Oid], [Maybe ByteString], [Int], [CInt])
-> Maybe (Oid, ByteString, Format)
-> ([Oid], [Maybe ByteString], [Int], [CInt]))
-> ([Oid], [Maybe ByteString], [Int], [CInt])
-> [Maybe (Oid, ByteString, Format)]
-> ([Oid], [Maybe ByteString], [Int], [CInt])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([Oid], [Maybe ByteString], [Int], [CInt])
-> Maybe (Oid, ByteString, Format)
-> ([Oid], [Maybe ByteString], [Int], [CInt])
forall a a.
(Num a, Enum a, Enum a) =>
([Oid], [Maybe ByteString], [Int], [a])
-> Maybe (Oid, ByteString, a)
-> ([Oid], [Maybe ByteString], [Int], [a])
accum ([],[],[],[]) ([Maybe (Oid, ByteString, Format)]
-> ([Oid], [Maybe ByteString], [Int], [CInt]))
-> [Maybe (Oid, ByteString, Format)]
-> ([Oid], [Maybe ByteString], [Int], [CInt])
forall a b. (a -> b) -> a -> b
$ [Maybe (Oid, ByteString, Format)]
-> [Maybe (Oid, ByteString, Format)]
forall a. [a] -> [a]
reverse [Maybe (Oid, ByteString, Format)]
params
!c_lengths :: [CInt]
c_lengths = (Int -> CInt) -> [Int] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CInt
forall a. Enum a => Int -> a
toEnum [Int]
lengths :: [CInt]
!n :: CInt
n = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Maybe (Oid, ByteString, Format)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Maybe (Oid, ByteString, Format)]
params
!f :: CInt
f = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Format -> Int
forall a. Enum a => a -> Int
fromEnum Format
rFmt
Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection ((Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result))
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
statement ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CString
s ->
[Oid] -> (Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [Oid]
oids ((Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr Oid
ts ->
(Maybe ByteString
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> [Maybe ByteString]
-> ([CString] -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany ((ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> Maybe ByteString
-> (CString -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString) [Maybe ByteString]
values (([CString] -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> ([CString] -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
[CString]
-> (Ptr CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CString]
c_values ((Ptr CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
[CInt] -> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
c_lengths ((Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
[CInt] -> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
formats ((Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
fs ->
Ptr PGconn
-> CString
-> CInt
-> Ptr Oid
-> Ptr CString
-> Ptr CInt
-> Ptr CInt
-> CInt
-> IO (Ptr PGresult)
c_PQexecParams Ptr PGconn
c CString
s CInt
n Ptr Oid
ts Ptr CString
vs Ptr CInt
ls Ptr CInt
fs CInt
f
where
accum :: ([Oid], [Maybe ByteString], [Int], [a])
-> Maybe (Oid, ByteString, a)
-> ([Oid], [Maybe ByteString], [Int], [a])
accum (![Oid]
a,![Maybe ByteString]
b,![Int]
c,![a]
d) Maybe (Oid, ByteString, a)
Nothing = ( Oid
invalidOidOid -> [Oid] -> [Oid]
forall a. a -> [a] -> [a]
:[Oid]
a
, Maybe ByteString
forall a. Maybe a
NothingMaybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
b
, Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
c
, a
0a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
d
)
accum (![Oid]
a,![Maybe ByteString]
b,![Int]
c,![a]
d) (Just (Oid
t,ByteString
v,a
f)) = ( Oid
tOid -> [Oid] -> [Oid]
forall a. a -> [a] -> [a]
:[Oid]
a
, (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
v)Maybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
b
, (ByteString -> Int
B.length ByteString
v)Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
c
, (Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
f)a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
d
)
prepare :: Connection
-> B.ByteString
-> B.ByteString
-> Maybe [Oid]
-> IO (Maybe Result)
prepare :: Connection
-> ByteString -> ByteString -> Maybe [Oid] -> IO (Maybe Result)
prepare Connection
connection ByteString
stmtName ByteString
query Maybe [Oid]
mParamTypes =
Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection ((Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result))
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CString
s ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CString
q ->
([Oid] -> (Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> Maybe [Oid]
-> (Ptr Oid -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith [Oid] -> (Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray Maybe [Oid]
mParamTypes ((Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr Oid
o ->
let l :: CInt
l = CInt -> ([Oid] -> CInt) -> Maybe [Oid] -> CInt
forall b a. b -> (a -> b) -> Maybe a -> b
maybe CInt
0 (Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> ([Oid] -> Int) -> [Oid] -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Oid] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) Maybe [Oid]
mParamTypes
in Ptr PGconn
-> CString -> CString -> CInt -> Ptr Oid -> IO (Ptr PGresult)
c_PQprepare Ptr PGconn
c CString
s CString
q CInt
l Ptr Oid
o
execPrepared :: Connection
-> B.ByteString
-> [Maybe (B.ByteString, Format)]
-> Format
-> IO (Maybe Result)
execPrepared :: Connection
-> ByteString
-> [Maybe (ByteString, Format)]
-> Format
-> IO (Maybe Result)
execPrepared Connection
connection ByteString
stmtName [Maybe (ByteString, Format)]
mPairs Format
rFmt =
do let ([Maybe ByteString]
values, [Int]
lengths, [CInt]
formats) = (([Maybe ByteString], [Int], [CInt])
-> Maybe (ByteString, Format)
-> ([Maybe ByteString], [Int], [CInt]))
-> ([Maybe ByteString], [Int], [CInt])
-> [Maybe (ByteString, Format)]
-> ([Maybe ByteString], [Int], [CInt])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([Maybe ByteString], [Int], [CInt])
-> Maybe (ByteString, Format)
-> ([Maybe ByteString], [Int], [CInt])
forall a a.
(Num a, Enum a, Enum a) =>
([Maybe ByteString], [Int], [a])
-> Maybe (ByteString, a) -> ([Maybe ByteString], [Int], [a])
accum ([],[],[]) ([Maybe (ByteString, Format)]
-> ([Maybe ByteString], [Int], [CInt]))
-> [Maybe (ByteString, Format)]
-> ([Maybe ByteString], [Int], [CInt])
forall a b. (a -> b) -> a -> b
$ [Maybe (ByteString, Format)] -> [Maybe (ByteString, Format)]
forall a. [a] -> [a]
reverse [Maybe (ByteString, Format)]
mPairs
!c_lengths :: [CInt]
c_lengths = (Int -> CInt) -> [Int] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CInt
forall a. Enum a => Int -> a
toEnum [Int]
lengths :: [CInt]
!n :: CInt
n = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Maybe (ByteString, Format)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Maybe (ByteString, Format)]
mPairs
!f :: CInt
f = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Format -> Int
forall a. Enum a => a -> Int
fromEnum Format
rFmt
Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection ((Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result))
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CString
s ->
(Maybe ByteString
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> [Maybe ByteString]
-> ([CString] -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany ((ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> Maybe ByteString
-> (CString -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString) [Maybe ByteString]
values (([CString] -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> ([CString] -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
[CString]
-> (Ptr CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CString]
c_values ((Ptr CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
[CInt] -> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
c_lengths ((Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
[CInt] -> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
formats ((Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Ptr CInt -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
fs ->
Ptr PGconn
-> CString
-> CInt
-> Ptr CString
-> Ptr CInt
-> Ptr CInt
-> CInt
-> IO (Ptr PGresult)
c_PQexecPrepared Ptr PGconn
c CString
s CInt
n Ptr CString
vs Ptr CInt
ls Ptr CInt
fs CInt
f
where
accum :: ([Maybe ByteString], [Int], [a])
-> Maybe (ByteString, a) -> ([Maybe ByteString], [Int], [a])
accum (![Maybe ByteString]
a,![Int]
b,![a]
c) Maybe (ByteString, a)
Nothing = ( Maybe ByteString
forall a. Maybe a
NothingMaybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
a
, Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
b
, a
0a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
c
)
accum (![Maybe ByteString]
a,![Int]
b,![a]
c) (Just (ByteString
v, a
f)) = ( (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
v)Maybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
a
, (ByteString -> Int
B.length ByteString
v)Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
b
, (Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
f)a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
c
)
describePrepared :: Connection
-> B.ByteString
-> IO (Maybe Result)
describePrepared :: Connection -> ByteString -> IO (Maybe Result)
describePrepared Connection
connection ByteString
stmtName =
Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection ((Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result))
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CString
s -> Ptr PGconn -> CString -> IO (Ptr PGresult)
c_PQdescribePrepared Ptr PGconn
c CString
s
describePortal :: Connection
-> B.ByteString
-> IO (Maybe Result)
describePortal :: Connection -> ByteString -> IO (Maybe Result)
describePortal Connection
connection ByteString
portalName =
Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection ((Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result))
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
portalName ((CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (CString -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CString
p ->
Ptr PGconn -> CString -> IO (Ptr PGresult)
c_PQdescribePortal Ptr PGconn
c CString
p
data ExecStatus = EmptyQuery
| CommandOk
| TuplesOk
| CopyOut
| CopyIn
| CopyBoth
| BadResponse
| NonfatalError
| FatalError
| SingleTuple
deriving (ExecStatus -> ExecStatus -> Bool
(ExecStatus -> ExecStatus -> Bool)
-> (ExecStatus -> ExecStatus -> Bool) -> Eq ExecStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecStatus -> ExecStatus -> Bool
$c/= :: ExecStatus -> ExecStatus -> Bool
== :: ExecStatus -> ExecStatus -> Bool
$c== :: ExecStatus -> ExecStatus -> Bool
Eq, Int -> ExecStatus -> ShowS
[ExecStatus] -> ShowS
ExecStatus -> String
(Int -> ExecStatus -> ShowS)
-> (ExecStatus -> String)
-> ([ExecStatus] -> ShowS)
-> Show ExecStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecStatus] -> ShowS
$cshowList :: [ExecStatus] -> ShowS
show :: ExecStatus -> String
$cshow :: ExecStatus -> String
showsPrec :: Int -> ExecStatus -> ShowS
$cshowsPrec :: Int -> ExecStatus -> ShowS
Show)
instance Enum ExecStatus where
toEnum :: Int -> ExecStatus
toEnum (Int
0) = ExecStatus
EmptyQuery
{-# LINE 1008 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (1) = CommandOk
{-# LINE 1009 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (2) = TuplesOk
{-# LINE 1010 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (3) = CopyOut
{-# LINE 1011 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (4) = CopyIn
{-# LINE 1012 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (8) = CopyBoth
{-# LINE 1013 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (5) = BadResponse
{-# LINE 1014 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (6) = NonfatalError
{-# LINE 1015 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (7) = FatalError
{-# LINE 1016 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (9) = SingleTuple
{-# LINE 1017 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum _ = error "Database.PQ.Enum.ExecStatus.toEnum: bad argument"
fromEnum :: ExecStatus -> Int
fromEnum ExecStatus
EmptyQuery = (Int
0)
{-# LINE 1020 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum CommandOk = (1)
{-# LINE 1021 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum TuplesOk = (2)
{-# LINE 1022 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum CopyOut = (3)
{-# LINE 1023 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum CopyIn = (4)
{-# LINE 1024 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum CopyBoth = (8)
{-# LINE 1025 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum BadResponse = (5)
{-# LINE 1026 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum NonfatalError = (6)
{-# LINE 1027 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum FatalError = (7)
{-# LINE 1028 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum SingleTuple = (9)
{-# LINE 1029 "src/Database/PostgreSQL/LibPQ.hsc" #-}
resultStatus :: Result
-> IO ExecStatus
resultStatus :: Result -> IO ExecStatus
resultStatus Result
result = Result -> (Ptr PGresult -> IO CInt) -> IO ExecStatus
forall a b.
(Integral a, Enum b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
enumFromResult Result
result Ptr PGresult -> IO CInt
c_PQresultStatus
resStatus :: ExecStatus
-> IO B.ByteString
resStatus :: ExecStatus -> IO ByteString
resStatus ExecStatus
es =
do CString
cstr <- CInt -> IO CString
c_PQresStatus (CInt -> IO CString) -> CInt -> IO CString
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ ExecStatus -> Int
forall a. Enum a => a -> Int
fromEnum ExecStatus
es
CSize
len <- CString -> IO CSize
B.c_strlen CString
cstr
ForeignPtr Word8
fp <- Ptr Word8 -> IO (ForeignPtr Word8)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ (Ptr Word8 -> IO (ForeignPtr Word8))
-> Ptr Word8 -> IO (ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
cstr
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp Int
0 (Int -> ByteString) -> Int -> ByteString
forall a b. (a -> b) -> a -> b
$ CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
len
resultErrorMessage :: Result
-> IO (Maybe B.ByteString)
resultErrorMessage :: Result -> IO (Maybe ByteString)
resultErrorMessage = (Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO CString) -> Result -> IO (Maybe ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
maybeBsFromResult Ptr PGresult -> IO CString
c_PQresultErrorMessage
unsafeFreeResult :: Result -> IO ()
unsafeFreeResult :: Result -> IO ()
unsafeFreeResult (Result ForeignPtr PGresult
x) = ForeignPtr PGresult -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr ForeignPtr PGresult
x
data FieldCode = DiagSeverity
| DiagSqlstate
| DiagMessagePrimary
| DiagMessageDetail
| DiagMessageHint
| DiagStatementPosition
| DiagInternalPosition
| DiagInternalQuery
| DiagContext
| DiagSourceFile
| DiagSourceLine
| DiagSourceFunction
deriving (FieldCode -> FieldCode -> Bool
(FieldCode -> FieldCode -> Bool)
-> (FieldCode -> FieldCode -> Bool) -> Eq FieldCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldCode -> FieldCode -> Bool
$c/= :: FieldCode -> FieldCode -> Bool
== :: FieldCode -> FieldCode -> Bool
$c== :: FieldCode -> FieldCode -> Bool
Eq, Int -> FieldCode -> ShowS
[FieldCode] -> ShowS
FieldCode -> String
(Int -> FieldCode -> ShowS)
-> (FieldCode -> String)
-> ([FieldCode] -> ShowS)
-> Show FieldCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldCode] -> ShowS
$cshowList :: [FieldCode] -> ShowS
show :: FieldCode -> String
$cshow :: FieldCode -> String
showsPrec :: Int -> FieldCode -> ShowS
$cshowsPrec :: Int -> FieldCode -> ShowS
Show)
instance Enum FieldCode where
toEnum :: Int -> FieldCode
toEnum (Int
83) = FieldCode
DiagSeverity
{-# LINE 1142 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (67) = DiagSqlstate
{-# LINE 1143 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (77) = DiagMessagePrimary
{-# LINE 1144 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (68) = DiagMessageDetail
{-# LINE 1145 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (72) = DiagMessageHint
{-# LINE 1146 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (80) = DiagStatementPosition
{-# LINE 1147 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (112) = DiagInternalPosition
{-# LINE 1148 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (113) = DiagInternalQuery
{-# LINE 1149 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (87) = DiagContext
{-# LINE 1150 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (70) = DiagSourceFile
{-# LINE 1151 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (76) = DiagSourceLine
{-# LINE 1152 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (82) = DiagSourceFunction
{-# LINE 1153 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum _ = error "Database.PQ.Enum.FieldCode.toEnum: bad argument"
fromEnum :: FieldCode -> Int
fromEnum FieldCode
DiagSeverity = (Int
83)
{-# LINE 1156 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagSqlstate = (67)
{-# LINE 1157 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagMessagePrimary = (77)
{-# LINE 1158 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagMessageDetail = (68)
{-# LINE 1159 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagMessageHint = (72)
{-# LINE 1160 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagStatementPosition = (80)
{-# LINE 1161 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagInternalPosition = (112)
{-# LINE 1162 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagInternalQuery = (113)
{-# LINE 1163 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagContext = (87)
{-# LINE 1164 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagSourceFile = (70)
{-# LINE 1165 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagSourceLine = (76)
{-# LINE 1166 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum DiagSourceFunction = (82)
{-# LINE 1167 "src/Database/PostgreSQL/LibPQ.hsc" #-}
resultErrorField :: Result
-> FieldCode
-> IO (Maybe B.ByteString)
resultErrorField :: Result -> FieldCode -> IO (Maybe ByteString)
resultErrorField (Result ForeignPtr PGresult
fp) FieldCode
fieldcode =
ForeignPtr PGresult
-> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
forall a.
ForeignPtr a -> (Ptr a -> IO CString) -> IO (Maybe ByteString)
maybeBsFromForeignPtr ForeignPtr PGresult
fp ((Ptr PGresult -> IO CString) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
res ->
Ptr PGresult -> CInt -> IO CString
c_PQresultErrorField Ptr PGresult
res (CInt -> IO CString) -> CInt -> IO CString
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ FieldCode -> Int
forall a. Enum a => a -> Int
fromEnum FieldCode
fieldcode
ntuples :: Result
-> IO Row
ntuples :: Result -> IO Row
ntuples Result
res = Result -> (Ptr PGresult -> IO Row) -> IO Row
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res (Row -> IO Row
forall (m :: * -> *) a. Monad m => a -> m a
return (Row -> IO Row) -> (Ptr PGresult -> Row) -> Ptr PGresult -> IO Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Row
forall a. Integral a => a -> Row
toRow (CInt -> Row) -> (Ptr PGresult -> CInt) -> Ptr PGresult -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr PGresult -> CInt
c_PQntuples)
nfields :: Result
-> IO Column
nfields :: Result -> IO Column
nfields Result
res = Result -> (Ptr PGresult -> IO Column) -> IO Column
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res (Column -> IO Column
forall (m :: * -> *) a. Monad m => a -> m a
return (Column -> IO Column)
-> (Ptr PGresult -> Column) -> Ptr PGresult -> IO Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Column
forall a. Integral a => a -> Column
toColumn (CInt -> Column)
-> (Ptr PGresult -> CInt) -> Ptr PGresult -> Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr PGresult -> CInt
c_PQnfields)
newtype Column = Col CInt deriving (Column -> Column -> Bool
(Column -> Column -> Bool)
-> (Column -> Column -> Bool) -> Eq Column
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Column -> Column -> Bool
$c/= :: Column -> Column -> Bool
== :: Column -> Column -> Bool
$c== :: Column -> Column -> Bool
Eq, Eq Column
Eq Column
-> (Column -> Column -> Ordering)
-> (Column -> Column -> Bool)
-> (Column -> Column -> Bool)
-> (Column -> Column -> Bool)
-> (Column -> Column -> Bool)
-> (Column -> Column -> Column)
-> (Column -> Column -> Column)
-> Ord Column
Column -> Column -> Bool
Column -> Column -> Ordering
Column -> Column -> Column
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Column -> Column -> Column
$cmin :: Column -> Column -> Column
max :: Column -> Column -> Column
$cmax :: Column -> Column -> Column
>= :: Column -> Column -> Bool
$c>= :: Column -> Column -> Bool
> :: Column -> Column -> Bool
$c> :: Column -> Column -> Bool
<= :: Column -> Column -> Bool
$c<= :: Column -> Column -> Bool
< :: Column -> Column -> Bool
$c< :: Column -> Column -> Bool
compare :: Column -> Column -> Ordering
$ccompare :: Column -> Column -> Ordering
$cp1Ord :: Eq Column
Ord, Int -> Column -> ShowS
[Column] -> ShowS
Column -> String
(Int -> Column -> ShowS)
-> (Column -> String) -> ([Column] -> ShowS) -> Show Column
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Column] -> ShowS
$cshowList :: [Column] -> ShowS
show :: Column -> String
$cshow :: Column -> String
showsPrec :: Int -> Column -> ShowS
$cshowsPrec :: Int -> Column -> ShowS
Show, Int -> Column
Column -> Int
Column -> [Column]
Column -> Column
Column -> Column -> [Column]
Column -> Column -> Column -> [Column]
(Column -> Column)
-> (Column -> Column)
-> (Int -> Column)
-> (Column -> Int)
-> (Column -> [Column])
-> (Column -> Column -> [Column])
-> (Column -> Column -> [Column])
-> (Column -> Column -> Column -> [Column])
-> Enum Column
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Column -> Column -> Column -> [Column]
$cenumFromThenTo :: Column -> Column -> Column -> [Column]
enumFromTo :: Column -> Column -> [Column]
$cenumFromTo :: Column -> Column -> [Column]
enumFromThen :: Column -> Column -> [Column]
$cenumFromThen :: Column -> Column -> [Column]
enumFrom :: Column -> [Column]
$cenumFrom :: Column -> [Column]
fromEnum :: Column -> Int
$cfromEnum :: Column -> Int
toEnum :: Int -> Column
$ctoEnum :: Int -> Column
pred :: Column -> Column
$cpred :: Column -> Column
succ :: Column -> Column
$csucc :: Column -> Column
Enum, Integer -> Column
Column -> Column
Column -> Column -> Column
(Column -> Column -> Column)
-> (Column -> Column -> Column)
-> (Column -> Column -> Column)
-> (Column -> Column)
-> (Column -> Column)
-> (Column -> Column)
-> (Integer -> Column)
-> Num Column
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Column
$cfromInteger :: Integer -> Column
signum :: Column -> Column
$csignum :: Column -> Column
abs :: Column -> Column
$cabs :: Column -> Column
negate :: Column -> Column
$cnegate :: Column -> Column
* :: Column -> Column -> Column
$c* :: Column -> Column -> Column
- :: Column -> Column -> Column
$c- :: Column -> Column -> Column
+ :: Column -> Column -> Column
$c+ :: Column -> Column -> Column
Num)
newtype Row = Row CInt deriving (Row -> Row -> Bool
(Row -> Row -> Bool) -> (Row -> Row -> Bool) -> Eq Row
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Row -> Row -> Bool
$c/= :: Row -> Row -> Bool
== :: Row -> Row -> Bool
$c== :: Row -> Row -> Bool
Eq, Eq Row
Eq Row
-> (Row -> Row -> Ordering)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Row)
-> (Row -> Row -> Row)
-> Ord Row
Row -> Row -> Bool
Row -> Row -> Ordering
Row -> Row -> Row
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Row -> Row -> Row
$cmin :: Row -> Row -> Row
max :: Row -> Row -> Row
$cmax :: Row -> Row -> Row
>= :: Row -> Row -> Bool
$c>= :: Row -> Row -> Bool
> :: Row -> Row -> Bool
$c> :: Row -> Row -> Bool
<= :: Row -> Row -> Bool
$c<= :: Row -> Row -> Bool
< :: Row -> Row -> Bool
$c< :: Row -> Row -> Bool
compare :: Row -> Row -> Ordering
$ccompare :: Row -> Row -> Ordering
$cp1Ord :: Eq Row
Ord, Int -> Row -> ShowS
[Row] -> ShowS
Row -> String
(Int -> Row -> ShowS)
-> (Row -> String) -> ([Row] -> ShowS) -> Show Row
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Row] -> ShowS
$cshowList :: [Row] -> ShowS
show :: Row -> String
$cshow :: Row -> String
showsPrec :: Int -> Row -> ShowS
$cshowsPrec :: Int -> Row -> ShowS
Show, Int -> Row
Row -> Int
Row -> [Row]
Row -> Row
Row -> Row -> [Row]
Row -> Row -> Row -> [Row]
(Row -> Row)
-> (Row -> Row)
-> (Int -> Row)
-> (Row -> Int)
-> (Row -> [Row])
-> (Row -> Row -> [Row])
-> (Row -> Row -> [Row])
-> (Row -> Row -> Row -> [Row])
-> Enum Row
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Row -> Row -> Row -> [Row]
$cenumFromThenTo :: Row -> Row -> Row -> [Row]
enumFromTo :: Row -> Row -> [Row]
$cenumFromTo :: Row -> Row -> [Row]
enumFromThen :: Row -> Row -> [Row]
$cenumFromThen :: Row -> Row -> [Row]
enumFrom :: Row -> [Row]
$cenumFrom :: Row -> [Row]
fromEnum :: Row -> Int
$cfromEnum :: Row -> Int
toEnum :: Int -> Row
$ctoEnum :: Int -> Row
pred :: Row -> Row
$cpred :: Row -> Row
succ :: Row -> Row
$csucc :: Row -> Row
Enum, Integer -> Row
Row -> Row
Row -> Row -> Row
(Row -> Row -> Row)
-> (Row -> Row -> Row)
-> (Row -> Row -> Row)
-> (Row -> Row)
-> (Row -> Row)
-> (Row -> Row)
-> (Integer -> Row)
-> Num Row
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Row
$cfromInteger :: Integer -> Row
signum :: Row -> Row
$csignum :: Row -> Row
abs :: Row -> Row
$cabs :: Row -> Row
negate :: Row -> Row
$cnegate :: Row -> Row
* :: Row -> Row -> Row
$c* :: Row -> Row -> Row
- :: Row -> Row -> Row
$c- :: Row -> Row -> Row
+ :: Row -> Row -> Row
$c+ :: Row -> Row -> Row
Num)
toColumn :: (Integral a) => a -> Column
toColumn :: a -> Column
toColumn = CInt -> Column
Col (CInt -> Column) -> (a -> CInt) -> a -> Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral
toRow :: (Integral a) => a -> Row
toRow :: a -> Row
toRow = CInt -> Row
Row (CInt -> Row) -> (a -> CInt) -> a -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fname :: Result
-> Column
-> IO (Maybe B.ByteString)
fname :: Result -> Column -> IO (Maybe ByteString)
fname Result
result (Col CInt
colNum) =
Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
maybeBsFromResult Result
result ((Ptr PGresult -> IO CString) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
fp ->
Ptr PGresult -> CInt -> IO CString
c_PQfname Ptr PGresult
fp CInt
colNum
fnumber :: Result
-> B.ByteString
-> IO (Maybe Column)
fnumber :: Result -> ByteString -> IO (Maybe Column)
fnumber Result
res ByteString
columnName =
do CInt
num <- Result -> (Ptr PGresult -> IO CInt) -> IO CInt
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res ((Ptr PGresult -> IO CInt) -> IO CInt)
-> (Ptr PGresult -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
resPtr ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
columnName ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
columnNamePtr ->
Ptr PGresult -> CString -> IO CInt
c_PQfnumber Ptr PGresult
resPtr CString
columnNamePtr
if CInt
num CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1
then Maybe Column -> IO (Maybe Column)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Column
forall a. Maybe a
Nothing
else Maybe Column -> IO (Maybe Column)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Column -> IO (Maybe Column))
-> Maybe Column -> IO (Maybe Column)
forall a b. (a -> b) -> a -> b
$ Column -> Maybe Column
forall a. a -> Maybe a
Just (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$ CInt -> Column
forall a. Integral a => a -> Column
toColumn CInt
num
ftable :: Result
-> Column
-> IO Oid
ftable :: Result -> Column -> IO Oid
ftable Result
result (Col CInt
colNum) = Result -> (Ptr PGresult -> IO Oid) -> IO Oid
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result ((Ptr PGresult -> IO Oid) -> IO Oid)
-> (Ptr PGresult -> IO Oid) -> IO Oid
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> Ptr PGresult -> CInt -> IO Oid
c_PQftable Ptr PGresult
ptr CInt
colNum
ftablecol :: Result
-> Column
-> IO Column
ftablecol :: Result -> Column -> IO Column
ftablecol Result
result (Col CInt
colNum) =
(CInt -> Column) -> IO CInt -> IO Column
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Column
Col (IO CInt -> IO Column) -> IO CInt -> IO Column
forall a b. (a -> b) -> a -> b
$ Result -> (Ptr PGresult -> IO CInt) -> IO CInt
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result ((Ptr PGresult -> IO CInt) -> IO CInt)
-> (Ptr PGresult -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
p -> Ptr PGresult -> CInt -> IO CInt
c_PQftablecol Ptr PGresult
p CInt
colNum
fformat :: Result
-> Column
-> IO Format
fformat :: Result -> Column -> IO Format
fformat Result
result (Col CInt
colNum) =
Result -> (Ptr PGresult -> IO CInt) -> IO Format
forall a b.
(Integral a, Enum b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
enumFromResult Result
result ((Ptr PGresult -> IO CInt) -> IO Format)
-> (Ptr PGresult -> IO CInt) -> IO Format
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> Ptr PGresult -> CInt -> IO CInt
c_PQfformat Ptr PGresult
ptr CInt
colNum
ftype :: Result
-> Column
-> IO Oid
ftype :: Result -> Column -> IO Oid
ftype Result
result (Col CInt
colNum) = Result -> (Ptr PGresult -> IO Oid) -> IO Oid
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result ((Ptr PGresult -> IO Oid) -> IO Oid)
-> (Ptr PGresult -> IO Oid) -> IO Oid
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> Ptr PGresult -> CInt -> IO Oid
c_PQftype Ptr PGresult
ptr CInt
colNum
fmod :: Result
-> Column
-> IO Int
fmod :: Result -> Column -> IO Int
fmod Result
result (Col CInt
colNum) = Result -> (Ptr PGresult -> IO CInt) -> IO Int
forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result ((Ptr PGresult -> IO CInt) -> IO Int)
-> (Ptr PGresult -> IO CInt) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> Ptr PGresult -> CInt -> IO CInt
c_PQfmod Ptr PGresult
ptr CInt
colNum
fsize :: Result
-> Column
-> IO Int
fsize :: Result -> Column -> IO Int
fsize Result
result (Col CInt
colNum) = Result -> (Ptr PGresult -> IO CInt) -> IO Int
forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result ((Ptr PGresult -> IO CInt) -> IO Int)
-> (Ptr PGresult -> IO CInt) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> Ptr PGresult -> CInt -> IO CInt
c_PQfsize Ptr PGresult
ptr CInt
colNum
getvalue :: Result
-> Row
-> Column
-> IO (Maybe B.ByteString)
getvalue :: Result -> Row -> Column -> IO (Maybe ByteString)
getvalue (Result ForeignPtr PGresult
fp) (Row CInt
rowNum) (Col CInt
colNum) =
ForeignPtr PGresult
-> (Ptr PGresult -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr PGresult
fp ((Ptr PGresult -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> do
CInt
isnull <- Ptr PGresult -> CInt -> CInt -> IO CInt
c_PQgetisnull Ptr PGresult
ptr CInt
rowNum CInt
colNum
if Int -> Bool
forall a. Enum a => Int -> a
toEnum (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
isnull
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ Maybe ByteString
forall a. Maybe a
Nothing
else do CString
cstr <- Ptr PGresult -> CInt -> CInt -> IO CString
c_PQgetvalue Ptr PGresult
ptr CInt
rowNum CInt
colNum
CInt
l <- Ptr PGresult -> CInt -> CInt -> IO CInt
c_PQgetlength Ptr PGresult
ptr CInt
rowNum CInt
colNum
ForeignPtr Word8
fp' <- Ptr Word8 -> IO () -> IO (ForeignPtr Word8)
forall a. Ptr a -> IO () -> IO (ForeignPtr a)
FC.newForeignPtr (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
cstr) IO ()
finalizer
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp' Int
0 (Int -> ByteString) -> Int -> ByteString
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
l
where
finalizer :: IO ()
finalizer = ForeignPtr PGresult -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr PGresult
fp
getvalue' :: Result
-> Row
-> Column
-> IO (Maybe B.ByteString)
getvalue' :: Result -> Row -> Column -> IO (Maybe ByteString)
getvalue' Result
res (Row CInt
rowNum) (Col CInt
colNum) =
Result
-> (Ptr PGresult -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res ((Ptr PGresult -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr -> do
CInt
isnull <- Ptr PGresult -> CInt -> CInt -> IO CInt
c_PQgetisnull Ptr PGresult
ptr CInt
rowNum CInt
colNum
if Int -> Bool
forall a. Enum a => Int -> a
toEnum (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
isnull
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ Maybe ByteString
forall a. Maybe a
Nothing
else do CString
cstr <- Ptr PGresult -> CInt -> CInt -> IO CString
c_PQgetvalue Ptr PGresult
ptr CInt
rowNum CInt
colNum
Int
l <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr PGresult -> CInt -> CInt -> IO CInt
c_PQgetlength Ptr PGresult
ptr CInt
rowNum CInt
colNum
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CStringLen -> IO ByteString
B.packCStringLen (CString
cstr, Int
l)
getisnull :: Result
-> Row
-> Column
-> IO Bool
getisnull :: Result -> Row -> Column -> IO Bool
getisnull Result
result (Row CInt
rowNum) (Col CInt
colNum) =
Result -> (Ptr PGresult -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
enumFromResult Result
result ((Ptr PGresult -> IO CInt) -> IO Bool)
-> (Ptr PGresult -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr ->
Ptr PGresult -> CInt -> CInt -> IO CInt
c_PQgetisnull Ptr PGresult
ptr CInt
rowNum CInt
colNum
getlength :: Result
-> Row
-> Column
-> IO Int
getlength :: Result -> Row -> Column -> IO Int
getlength Result
result (Row CInt
rowNum) (Col CInt
colNum) =
Result -> (Ptr PGresult -> IO CInt) -> IO Int
forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result ((Ptr PGresult -> IO CInt) -> IO Int)
-> (Ptr PGresult -> IO CInt) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
ptr ->
Ptr PGresult -> CInt -> CInt -> IO CInt
c_PQgetlength Ptr PGresult
ptr CInt
rowNum CInt
colNum
nparams :: Result
-> IO Int
nparams :: Result -> IO Int
nparams Result
result = Result -> (Ptr PGresult -> IO CInt) -> IO Int
forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result Ptr PGresult -> IO CInt
c_PQnparams
paramtype :: Result
-> Int
-> IO Oid
paramtype :: Result -> Int -> IO Oid
paramtype Result
result Int
param_number =
Result -> (Ptr PGresult -> IO Oid) -> IO Oid
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result ((Ptr PGresult -> IO Oid) -> IO Oid)
-> (Ptr PGresult -> IO Oid) -> IO Oid
forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
p -> Ptr PGresult -> CInt -> IO Oid
c_PQparamtype Ptr PGresult
p (CInt -> IO Oid) -> CInt -> IO Oid
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
param_number
cmdStatus :: Result
-> IO (Maybe B.ByteString)
cmdStatus :: Result -> IO (Maybe ByteString)
cmdStatus = (Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO CString) -> Result -> IO (Maybe ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
maybeBsFromResult Ptr PGresult -> IO CString
c_PQcmdStatus
cmdTuples :: Result
-> IO (Maybe B.ByteString)
cmdTuples :: Result -> IO (Maybe ByteString)
cmdTuples = (Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString))
-> (Ptr PGresult -> IO CString) -> Result -> IO (Maybe ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
maybeBsFromResult Ptr PGresult -> IO CString
c_PQcmdTuples
escapeStringConn :: Connection
-> B.ByteString
-> IO (Maybe B.ByteString)
escapeStringConn :: Connection -> ByteString -> IO (Maybe ByteString)
escapeStringConn Connection
connection ByteString
bs =
Connection
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
ByteString
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs ((CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \(CString
from, Int
bslen) ->
(Ptr CInt -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr CInt -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
err -> do
ByteString
xs <- Int -> (Ptr Word8 -> IO Int) -> IO ByteString
B.createAndTrim (Int
bslenInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr Word8 -> IO Int) -> IO ByteString)
-> (Ptr Word8 -> IO Int) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
to ->
CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int) -> IO CSize -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
Ptr PGconn -> Ptr Word8 -> CString -> CSize -> Ptr CInt -> IO CSize
c_PQescapeStringConn Ptr PGconn
conn Ptr Word8
to CString
from (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bslen) Ptr CInt
err
CInt
stat <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
err
case CInt
stat of
CInt
0 -> Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
xs
CInt
_ -> Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
escapeByteaConn :: Connection
-> B.ByteString
-> IO (Maybe B.ByteString)
escapeByteaConn :: Connection -> ByteString -> IO (Maybe ByteString)
escapeByteaConn Connection
connection ByteString
bs =
Connection
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
ByteString
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs ((CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \(CString
from, Int
bslen) ->
(Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
to_length -> do
Ptr Word8
to <- Ptr PGconn -> CString -> CSize -> Ptr CSize -> IO (Ptr Word8)
c_PQescapeByteaConn Ptr PGconn
conn CString
from (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bslen) Ptr CSize
to_length
if Ptr Word8
to Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do ForeignPtr Word8
tofp <- FinalizerPtr Word8 -> Ptr Word8 -> IO (ForeignPtr Word8)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Word8
forall a. FunPtr (Ptr a -> IO ())
p_PQfreemem Ptr Word8
to
CSize
l <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
to_length
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
tofp Int
0 ((CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
l) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
unescapeBytea :: B.ByteString
-> IO (Maybe B.ByteString)
unescapeBytea :: ByteString -> IO (Maybe ByteString)
unescapeBytea ByteString
bs =
ByteString
-> (CString -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
bs ((CString -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (CString -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \CString
from ->
(Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
to_length -> do
Ptr Word8
to <- CString -> Ptr CSize -> IO (Ptr Word8)
c_PQunescapeBytea CString
from Ptr CSize
to_length
if Ptr Word8
to Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do ForeignPtr Word8
tofp <- FinalizerPtr Word8 -> Ptr Word8 -> IO (ForeignPtr Word8)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Word8
forall a. FunPtr (Ptr a -> IO ())
p_PQfreemem Ptr Word8
to
CSize
l <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
to_length
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
tofp Int
0 (Int -> ByteString) -> Int -> ByteString
forall a b. (a -> b) -> a -> b
$ CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
l
escapeIdentifier :: Connection
-> B.ByteString
-> IO (Maybe B.ByteString)
escapeIdentifier :: Connection -> ByteString -> IO (Maybe ByteString)
escapeIdentifier Connection
connection ByteString
bs =
Connection
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
ByteString
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs ((CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \(CString
from, Int
bslen) -> IO (Maybe ByteString) -> IO (Maybe ByteString)
forall a. IO a -> IO a
mask_ (IO (Maybe ByteString) -> IO (Maybe ByteString))
-> IO (Maybe ByteString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ do
CString
bs'ptr <- Ptr PGconn -> CString -> CSize -> IO CString
c_PQescapeIdentifier Ptr PGconn
conn CString
from (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bslen)
if CString
bs'ptr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do
ByteString
bs' <- CString -> IO ByteString
B.packCString CString
bs'ptr
CString -> IO ()
forall a. Ptr a -> IO ()
c_PQfreemem CString
bs'ptr
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bs'
data CopyInResult
= CopyInOk
| CopyInError
| CopyInWouldBlock
deriving (CopyInResult -> CopyInResult -> Bool
(CopyInResult -> CopyInResult -> Bool)
-> (CopyInResult -> CopyInResult -> Bool) -> Eq CopyInResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyInResult -> CopyInResult -> Bool
$c/= :: CopyInResult -> CopyInResult -> Bool
== :: CopyInResult -> CopyInResult -> Bool
$c== :: CopyInResult -> CopyInResult -> Bool
Eq, Int -> CopyInResult -> ShowS
[CopyInResult] -> ShowS
CopyInResult -> String
(Int -> CopyInResult -> ShowS)
-> (CopyInResult -> String)
-> ([CopyInResult] -> ShowS)
-> Show CopyInResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyInResult] -> ShowS
$cshowList :: [CopyInResult] -> ShowS
show :: CopyInResult -> String
$cshow :: CopyInResult -> String
showsPrec :: Int -> CopyInResult -> ShowS
$cshowsPrec :: Int -> CopyInResult -> ShowS
Show)
toCopyInResult :: CInt -> IO CopyInResult
toCopyInResult :: CInt -> IO CopyInResult
toCopyInResult CInt
n | CInt
n CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0 = CopyInResult -> IO CopyInResult
forall (m :: * -> *) a. Monad m => a -> m a
return CopyInResult
CopyInError
| CInt
n CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0 = CopyInResult -> IO CopyInResult
forall (m :: * -> *) a. Monad m => a -> m a
return CopyInResult
CopyInWouldBlock
| Bool
otherwise = CopyInResult -> IO CopyInResult
forall (m :: * -> *) a. Monad m => a -> m a
return CopyInResult
CopyInOk
putCopyData :: Connection -> B.ByteString -> IO CopyInResult
putCopyData :: Connection -> ByteString -> IO CopyInResult
putCopyData Connection
conn ByteString
bs =
ByteString -> (CStringLen -> IO CopyInResult) -> IO CopyInResult
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs ((CStringLen -> IO CopyInResult) -> IO CopyInResult)
-> (CStringLen -> IO CopyInResult) -> IO CopyInResult
forall a b. (a -> b) -> a -> b
$ Connection -> CStringLen -> IO CopyInResult
putCopyCString Connection
conn
putCopyCString :: Connection -> CStringLen -> IO CopyInResult
putCopyCString :: Connection -> CStringLen -> IO CopyInResult
putCopyCString Connection
conn (CString
str, Int
len) =
CInt -> IO CopyInResult
toCopyInResult (CInt -> IO CopyInResult) -> IO CInt -> IO CopyInResult
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
(Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn ((Ptr PGconn -> IO CInt) -> IO CInt)
-> (Ptr PGconn -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CString -> CInt -> IO CInt
c_PQputCopyData Ptr PGconn
ptr CString
str (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len))
putCopyEnd :: Connection -> Maybe B.ByteString -> IO CopyInResult
putCopyEnd :: Connection -> Maybe ByteString -> IO CopyInResult
putCopyEnd Connection
conn Maybe ByteString
Nothing =
CInt -> IO CopyInResult
toCopyInResult (CInt -> IO CopyInResult) -> IO CInt -> IO CopyInResult
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
(Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn ((Ptr PGconn -> IO CInt) -> IO CInt)
-> (Ptr PGconn -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CString -> IO CInt
c_PQputCopyEnd Ptr PGconn
ptr CString
forall a. Ptr a
nullPtr)
putCopyEnd Connection
conn (Just ByteString
errormsg) =
CInt -> IO CopyInResult
toCopyInResult (CInt -> IO CopyInResult) -> IO CInt -> IO CopyInResult
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
(ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
errormsg ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
errormsg_cstr ->
Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn ((Ptr PGconn -> IO CInt) -> IO CInt)
-> (Ptr PGconn -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CString -> IO CInt
c_PQputCopyEnd Ptr PGconn
ptr CString
errormsg_cstr)
data CopyOutResult
= CopyOutRow !B.ByteString
| CopyOutWouldBlock
| CopyOutDone
| CopyOutError
deriving Int -> CopyOutResult -> ShowS
[CopyOutResult] -> ShowS
CopyOutResult -> String
(Int -> CopyOutResult -> ShowS)
-> (CopyOutResult -> String)
-> ([CopyOutResult] -> ShowS)
-> Show CopyOutResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyOutResult] -> ShowS
$cshowList :: [CopyOutResult] -> ShowS
show :: CopyOutResult -> String
$cshow :: CopyOutResult -> String
showsPrec :: Int -> CopyOutResult -> ShowS
$cshowsPrec :: Int -> CopyOutResult -> ShowS
Show
getCopyData :: Connection -> Bool -> IO CopyOutResult
getCopyData :: Connection -> Bool -> IO CopyOutResult
getCopyData Connection
conn Bool
async = (Ptr (Ptr Word8) -> IO CopyOutResult) -> IO CopyOutResult
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr Word8) -> IO CopyOutResult) -> IO CopyOutResult)
-> (Ptr (Ptr Word8) -> IO CopyOutResult) -> IO CopyOutResult
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr Word8)
strp -> Connection -> (Ptr PGconn -> IO CopyOutResult) -> IO CopyOutResult
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn ((Ptr PGconn -> IO CopyOutResult) -> IO CopyOutResult)
-> (Ptr PGconn -> IO CopyOutResult) -> IO CopyOutResult
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt
len <- Ptr PGconn -> Ptr (Ptr Word8) -> CInt -> IO CInt
c_PQgetCopyData Ptr PGconn
c Ptr (Ptr Word8)
strp (CInt -> IO CInt) -> CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$! (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Bool -> Int
forall a. Enum a => a -> Int
fromEnum Bool
async))
if CInt
len CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
<= CInt
0
then case CInt -> CInt -> Ordering
forall a. Ord a => a -> a -> Ordering
compare CInt
len (-CInt
1) of
Ordering
LT -> CopyOutResult -> IO CopyOutResult
forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutError
Ordering
EQ -> CopyOutResult -> IO CopyOutResult
forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutDone
Ordering
GT -> CopyOutResult -> IO CopyOutResult
forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutWouldBlock
else do
ForeignPtr Word8
fp <- FinalizerPtr Word8 -> Ptr Word8 -> IO (ForeignPtr Word8)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Word8
forall a. FunPtr (Ptr a -> IO ())
p_PQfreemem (Ptr Word8 -> IO (ForeignPtr Word8))
-> IO (Ptr Word8) -> IO (ForeignPtr Word8)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Word8) -> IO (Ptr Word8)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Word8)
strp
CopyOutResult -> IO CopyOutResult
forall (m :: * -> *) a. Monad m => a -> m a
return (CopyOutResult -> IO CopyOutResult)
-> CopyOutResult -> IO CopyOutResult
forall a b. (a -> b) -> a -> b
$! ByteString -> CopyOutResult
CopyOutRow (ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp Int
0 (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len))
sendQuery :: Connection
-> B.ByteString
-> IO Bool
sendQuery :: Connection -> ByteString -> IO Bool
sendQuery Connection
connection ByteString
query =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Bool)
-> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
p ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr PGconn -> CString -> IO CInt
c_PQsendQuery Ptr PGconn
p
sendQueryParams :: Connection
-> B.ByteString
-> [Maybe (Oid, B.ByteString, Format)]
-> Format
-> IO Bool
sendQueryParams :: Connection
-> ByteString
-> [Maybe (Oid, ByteString, Format)]
-> Format
-> IO Bool
sendQueryParams Connection
connection ByteString
statement [Maybe (Oid, ByteString, Format)]
params Format
rFmt =
do let ([Oid]
oids, [Maybe ByteString]
values, [Int]
lengths, [CInt]
formats) =
(([Oid], [Maybe ByteString], [Int], [CInt])
-> Maybe (Oid, ByteString, Format)
-> ([Oid], [Maybe ByteString], [Int], [CInt]))
-> ([Oid], [Maybe ByteString], [Int], [CInt])
-> [Maybe (Oid, ByteString, Format)]
-> ([Oid], [Maybe ByteString], [Int], [CInt])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([Oid], [Maybe ByteString], [Int], [CInt])
-> Maybe (Oid, ByteString, Format)
-> ([Oid], [Maybe ByteString], [Int], [CInt])
forall a a.
(Num a, Enum a, Enum a) =>
([Oid], [Maybe ByteString], [Int], [a])
-> Maybe (Oid, ByteString, a)
-> ([Oid], [Maybe ByteString], [Int], [a])
accum ([],[],[],[]) ([Maybe (Oid, ByteString, Format)]
-> ([Oid], [Maybe ByteString], [Int], [CInt]))
-> [Maybe (Oid, ByteString, Format)]
-> ([Oid], [Maybe ByteString], [Int], [CInt])
forall a b. (a -> b) -> a -> b
$ [Maybe (Oid, ByteString, Format)]
-> [Maybe (Oid, ByteString, Format)]
forall a. [a] -> [a]
reverse [Maybe (Oid, ByteString, Format)]
params
!c_lengths :: [CInt]
c_lengths = (Int -> CInt) -> [Int] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CInt
forall a. Enum a => Int -> a
toEnum [Int]
lengths :: [CInt]
!n :: CInt
n = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Maybe (Oid, ByteString, Format)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Maybe (Oid, ByteString, Format)]
params
!f :: CInt
f = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Format -> Int
forall a. Enum a => a -> Int
fromEnum Format
rFmt
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Bool)
-> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
statement ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
s ->
[Oid] -> (Ptr Oid -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [Oid]
oids ((Ptr Oid -> IO CInt) -> IO CInt)
-> (Ptr Oid -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr Oid
ts ->
(Maybe ByteString -> (CString -> IO CInt) -> IO CInt)
-> [Maybe ByteString] -> ([CString] -> IO CInt) -> IO CInt
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany ((ByteString -> (CString -> IO CInt) -> IO CInt)
-> Maybe ByteString -> (CString -> IO CInt) -> IO CInt
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString) [Maybe ByteString]
values (([CString] -> IO CInt) -> IO CInt)
-> ([CString] -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
[CString] -> (Ptr CString -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CString]
c_values ((Ptr CString -> IO CInt) -> IO CInt)
-> (Ptr CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
[CInt] -> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
c_lengths ((Ptr CInt -> IO CInt) -> IO CInt)
-> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
[CInt] -> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
formats ((Ptr CInt -> IO CInt) -> IO CInt)
-> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
fs ->
Ptr PGconn
-> CString
-> CInt
-> Ptr Oid
-> Ptr CString
-> Ptr CInt
-> Ptr CInt
-> CInt
-> IO CInt
c_PQsendQueryParams Ptr PGconn
c CString
s CInt
n Ptr Oid
ts Ptr CString
vs Ptr CInt
ls Ptr CInt
fs CInt
f
where
accum :: ([Oid], [Maybe ByteString], [Int], [a])
-> Maybe (Oid, ByteString, a)
-> ([Oid], [Maybe ByteString], [Int], [a])
accum (![Oid]
a,![Maybe ByteString]
b,![Int]
c,![a]
d) Maybe (Oid, ByteString, a)
Nothing = ( Oid
invalidOidOid -> [Oid] -> [Oid]
forall a. a -> [a] -> [a]
:[Oid]
a
, Maybe ByteString
forall a. Maybe a
NothingMaybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
b
, Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
c
, a
0a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
d
)
accum (![Oid]
a,![Maybe ByteString]
b,![Int]
c,![a]
d) (Just (Oid
t,ByteString
v,a
f)) = ( Oid
tOid -> [Oid] -> [Oid]
forall a. a -> [a] -> [a]
:[Oid]
a
, (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
v)Maybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
b
, (ByteString -> Int
B.length ByteString
v)Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
c
, (Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
f)a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
d
)
sendPrepare :: Connection
-> B.ByteString
-> B.ByteString
-> Maybe [Oid]
-> IO Bool
sendPrepare :: Connection -> ByteString -> ByteString -> Maybe [Oid] -> IO Bool
sendPrepare Connection
connection ByteString
stmtName ByteString
query Maybe [Oid]
mParamTypes =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Bool)
-> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
s ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
q ->
([Oid] -> (Ptr Oid -> IO CInt) -> IO CInt)
-> Maybe [Oid] -> (Ptr Oid -> IO CInt) -> IO CInt
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith [Oid] -> (Ptr Oid -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray Maybe [Oid]
mParamTypes ((Ptr Oid -> IO CInt) -> IO CInt)
-> (Ptr Oid -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr Oid
o ->
let l :: CInt
l = CInt -> ([Oid] -> CInt) -> Maybe [Oid] -> CInt
forall b a. b -> (a -> b) -> Maybe a -> b
maybe CInt
0 (Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> ([Oid] -> Int) -> [Oid] -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Oid] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) Maybe [Oid]
mParamTypes
in Ptr PGconn -> CString -> CString -> CInt -> Ptr Oid -> IO CInt
c_PQsendPrepare Ptr PGconn
c CString
s CString
q CInt
l Ptr Oid
o
sendQueryPrepared :: Connection
-> B.ByteString
-> [Maybe (B.ByteString, Format)]
-> Format
-> IO Bool
sendQueryPrepared :: Connection
-> ByteString -> [Maybe (ByteString, Format)] -> Format -> IO Bool
sendQueryPrepared Connection
connection ByteString
stmtName [Maybe (ByteString, Format)]
mPairs Format
rFmt =
do let ([Maybe ByteString]
values, [Int]
lengths, [CInt]
formats) = (([Maybe ByteString], [Int], [CInt])
-> Maybe (ByteString, Format)
-> ([Maybe ByteString], [Int], [CInt]))
-> ([Maybe ByteString], [Int], [CInt])
-> [Maybe (ByteString, Format)]
-> ([Maybe ByteString], [Int], [CInt])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([Maybe ByteString], [Int], [CInt])
-> Maybe (ByteString, Format)
-> ([Maybe ByteString], [Int], [CInt])
forall a a.
(Num a, Enum a, Enum a) =>
([Maybe ByteString], [Int], [a])
-> Maybe (ByteString, a) -> ([Maybe ByteString], [Int], [a])
accum ([],[],[]) ([Maybe (ByteString, Format)]
-> ([Maybe ByteString], [Int], [CInt]))
-> [Maybe (ByteString, Format)]
-> ([Maybe ByteString], [Int], [CInt])
forall a b. (a -> b) -> a -> b
$ [Maybe (ByteString, Format)] -> [Maybe (ByteString, Format)]
forall a. [a] -> [a]
reverse [Maybe (ByteString, Format)]
mPairs
!c_lengths :: [CInt]
c_lengths = (Int -> CInt) -> [Int] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CInt
forall a. Enum a => Int -> a
toEnum [Int]
lengths :: [CInt]
!n :: CInt
n = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Maybe (ByteString, Format)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Maybe (ByteString, Format)]
mPairs
!f :: CInt
f = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Format -> Int
forall a. Enum a => a -> Int
fromEnum Format
rFmt
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Bool)
-> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
s ->
(Maybe ByteString -> (CString -> IO CInt) -> IO CInt)
-> [Maybe ByteString] -> ([CString] -> IO CInt) -> IO CInt
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany ((ByteString -> (CString -> IO CInt) -> IO CInt)
-> Maybe ByteString -> (CString -> IO CInt) -> IO CInt
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString) [Maybe ByteString]
values (([CString] -> IO CInt) -> IO CInt)
-> ([CString] -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
[CString] -> (Ptr CString -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CString]
c_values ((Ptr CString -> IO CInt) -> IO CInt)
-> (Ptr CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
[CInt] -> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
c_lengths ((Ptr CInt -> IO CInt) -> IO CInt)
-> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
[CInt] -> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [CInt]
formats ((Ptr CInt -> IO CInt) -> IO CInt)
-> (Ptr CInt -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
fs ->
Ptr PGconn
-> CString
-> CInt
-> Ptr CString
-> Ptr CInt
-> Ptr CInt
-> CInt
-> IO CInt
c_PQsendQueryPrepared Ptr PGconn
c CString
s CInt
n Ptr CString
vs Ptr CInt
ls Ptr CInt
fs CInt
f
where
accum :: ([Maybe ByteString], [Int], [a])
-> Maybe (ByteString, a) -> ([Maybe ByteString], [Int], [a])
accum (![Maybe ByteString]
a,![Int]
b,![a]
c) Maybe (ByteString, a)
Nothing = ( Maybe ByteString
forall a. Maybe a
NothingMaybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
a
, Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
b
, a
0a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
c
)
accum (![Maybe ByteString]
a,![Int]
b,![a]
c) (Just (ByteString
v, a
f)) = ( (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
v)Maybe ByteString -> [Maybe ByteString] -> [Maybe ByteString]
forall a. a -> [a] -> [a]
:[Maybe ByteString]
a
, (ByteString -> Int
B.length ByteString
v)Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
b
, (Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
f)a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
c
)
sendDescribePrepared :: Connection
-> B.ByteString
-> IO Bool
sendDescribePrepared :: Connection -> ByteString -> IO Bool
sendDescribePrepared Connection
connection ByteString
stmtName =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Bool)
-> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
s ->
Ptr PGconn -> CString -> IO CInt
c_PQsendDescribePrepared Ptr PGconn
c CString
s
sendDescribePortal :: Connection
-> B.ByteString
-> IO Bool
sendDescribePortal :: Connection -> ByteString -> IO Bool
sendDescribePortal Connection
connection ByteString
portalName =
Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Bool)
-> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
portalName ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
p ->
Ptr PGconn -> CString -> IO CInt
c_PQsendDescribePortal Ptr PGconn
c CString
p
getResult :: Connection
-> IO (Maybe Result)
getResult :: Connection -> IO (Maybe Result)
getResult Connection
connection =
do Ptr PGresult
resPtr <- Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO (Ptr PGresult)
c_PQgetResult
if Ptr PGresult
resPtr Ptr PGresult -> Ptr PGresult -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGresult
forall a. Ptr a
nullPtr
then Maybe Result -> IO (Maybe Result)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Result
forall a. Maybe a
Nothing
else (Result -> Maybe Result
forall a. a -> Maybe a
Just (Result -> Maybe Result)
-> (ForeignPtr PGresult -> Result)
-> ForeignPtr PGresult
-> Maybe Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr PGresult -> Result
Result) (ForeignPtr PGresult -> Maybe Result)
-> IO (ForeignPtr PGresult) -> IO (Maybe Result)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` FinalizerPtr PGresult -> Ptr PGresult -> IO (ForeignPtr PGresult)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr PGresult
p_PQclear Ptr PGresult
resPtr
consumeInput :: Connection
-> IO Bool
consumeInput :: Connection -> IO Bool
consumeInput Connection
connection = Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQconsumeInput
isBusy :: Connection
-> IO Bool
isBusy :: Connection -> IO Bool
isBusy Connection
connection = Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQisBusy
setnonblocking :: Connection
-> Bool
-> IO Bool
setnonblocking :: Connection -> Bool -> IO Bool
setnonblocking Connection
connection Bool
blocking =
do let arg :: CInt
arg = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Bool -> Int
forall a. Enum a => a -> Int
fromEnum Bool
blocking
CInt
stat <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO CInt)
-> (Ptr PGconn -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CInt -> IO CInt
c_PQsetnonblocking Ptr PGconn
ptr CInt
arg
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! CInt
stat CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
isnonblocking :: Connection
-> IO Bool
isnonblocking :: Connection -> IO Bool
isnonblocking Connection
connection = Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQisnonblocking
setSingleRowMode :: Connection
-> IO Bool
setSingleRowMode :: Connection -> IO Bool
setSingleRowMode Connection
connection = Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
c_PQsetSingleRowMode
data FlushStatus = FlushOk
| FlushFailed
| FlushWriting
deriving (FlushStatus -> FlushStatus -> Bool
(FlushStatus -> FlushStatus -> Bool)
-> (FlushStatus -> FlushStatus -> Bool) -> Eq FlushStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlushStatus -> FlushStatus -> Bool
$c/= :: FlushStatus -> FlushStatus -> Bool
== :: FlushStatus -> FlushStatus -> Bool
$c== :: FlushStatus -> FlushStatus -> Bool
Eq, Int -> FlushStatus -> ShowS
[FlushStatus] -> ShowS
FlushStatus -> String
(Int -> FlushStatus -> ShowS)
-> (FlushStatus -> String)
-> ([FlushStatus] -> ShowS)
-> Show FlushStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlushStatus] -> ShowS
$cshowList :: [FlushStatus] -> ShowS
show :: FlushStatus -> String
$cshow :: FlushStatus -> String
showsPrec :: Int -> FlushStatus -> ShowS
$cshowsPrec :: Int -> FlushStatus -> ShowS
Show)
flush :: Connection
-> IO FlushStatus
flush :: Connection -> IO FlushStatus
flush Connection
connection =
do CInt
stat <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQflush
case CInt
stat of
CInt
0 -> FlushStatus -> IO FlushStatus
forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushOk
CInt
1 -> FlushStatus -> IO FlushStatus
forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushWriting
CInt
_ -> FlushStatus -> IO FlushStatus
forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushFailed
newtype Cancel = Cancel (ForeignPtr PGcancel) deriving (Cancel -> Cancel -> Bool
(Cancel -> Cancel -> Bool)
-> (Cancel -> Cancel -> Bool) -> Eq Cancel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cancel -> Cancel -> Bool
$c/= :: Cancel -> Cancel -> Bool
== :: Cancel -> Cancel -> Bool
$c== :: Cancel -> Cancel -> Bool
Eq, Int -> Cancel -> ShowS
[Cancel] -> ShowS
Cancel -> String
(Int -> Cancel -> ShowS)
-> (Cancel -> String) -> ([Cancel] -> ShowS) -> Show Cancel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cancel] -> ShowS
$cshowList :: [Cancel] -> ShowS
show :: Cancel -> String
$cshow :: Cancel -> String
showsPrec :: Int -> Cancel -> ShowS
$cshowsPrec :: Int -> Cancel -> ShowS
Show)
data PGcancel
getCancel :: Connection
-> IO (Maybe Cancel)
getCancel :: Connection -> IO (Maybe Cancel)
getCancel Connection
connection =
IO (Maybe Cancel) -> IO (Maybe Cancel)
forall a. IO a -> IO a
mask_ (IO (Maybe Cancel) -> IO (Maybe Cancel))
-> IO (Maybe Cancel) -> IO (Maybe Cancel)
forall a b. (a -> b) -> a -> b
$ Connection
-> (Ptr PGconn -> IO (Maybe Cancel)) -> IO (Maybe Cancel)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Cancel)) -> IO (Maybe Cancel))
-> (Ptr PGconn -> IO (Maybe Cancel)) -> IO (Maybe Cancel)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
do Ptr PGcancel
ptr <- Ptr PGconn -> IO (Ptr PGcancel)
c_PQgetCancel Ptr PGconn
conn
if Ptr PGcancel
ptr Ptr PGcancel -> Ptr PGcancel -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGcancel
forall a. Ptr a
nullPtr
then Maybe Cancel -> IO (Maybe Cancel)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Cancel
forall a. Maybe a
Nothing
else do ForeignPtr PGcancel
fp <- FinalizerPtr PGcancel -> Ptr PGcancel -> IO (ForeignPtr PGcancel)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr PGcancel
p_PQfreeCancel Ptr PGcancel
ptr
Maybe Cancel -> IO (Maybe Cancel)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Cancel -> IO (Maybe Cancel))
-> Maybe Cancel -> IO (Maybe Cancel)
forall a b. (a -> b) -> a -> b
$ Cancel -> Maybe Cancel
forall a. a -> Maybe a
Just (Cancel -> Maybe Cancel) -> Cancel -> Maybe Cancel
forall a b. (a -> b) -> a -> b
$ ForeignPtr PGcancel -> Cancel
Cancel ForeignPtr PGcancel
fp
cancel :: Cancel
-> IO (Either B.ByteString ())
cancel :: Cancel -> IO (Either ByteString ())
cancel (Cancel ForeignPtr PGcancel
fp) =
ForeignPtr PGcancel
-> (Ptr PGcancel -> IO (Either ByteString ()))
-> IO (Either ByteString ())
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr PGcancel
fp ((Ptr PGcancel -> IO (Either ByteString ()))
-> IO (Either ByteString ()))
-> (Ptr PGcancel -> IO (Either ByteString ()))
-> IO (Either ByteString ())
forall a b. (a -> b) -> a -> b
$ \Ptr PGcancel
ptr -> do
Int
-> (CString -> IO (Either ByteString ()))
-> IO (Either ByteString ())
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
errbufsize ((CString -> IO (Either ByteString ()))
-> IO (Either ByteString ()))
-> (CString -> IO (Either ByteString ()))
-> IO (Either ByteString ())
forall a b. (a -> b) -> a -> b
$ \CString
errbuf -> do
CInt
res <- Ptr PGcancel -> CString -> CInt -> IO CInt
c_PQcancel Ptr PGcancel
ptr CString
errbuf (CInt -> IO CInt) -> CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
errbufsize
case CInt
res of
CInt
1 -> Either ByteString () -> IO (Either ByteString ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString () -> IO (Either ByteString ()))
-> Either ByteString () -> IO (Either ByteString ())
forall a b. (a -> b) -> a -> b
$ () -> Either ByteString ()
forall a b. b -> Either a b
Right ()
CInt
_ -> ByteString -> Either ByteString ()
forall a b. a -> Either a b
Left (ByteString -> Either ByteString ())
-> IO ByteString -> IO (Either ByteString ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CString -> IO ByteString
B.packCString CString
errbuf
where
errbufsize :: Int
errbufsize = Int
256
data Notify = Notify {
Notify -> ByteString
notifyRelname :: {-# UNPACK #-} !B.ByteString
, Notify -> CPid
notifyBePid :: {-# UNPACK #-} !CPid
, :: {-# UNPACK #-} !B.ByteString
} deriving Int -> Notify -> ShowS
[Notify] -> ShowS
Notify -> String
(Int -> Notify -> ShowS)
-> (Notify -> String) -> ([Notify] -> ShowS) -> Show Notify
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Notify] -> ShowS
$cshowList :: [Notify] -> ShowS
show :: Notify -> String
$cshow :: Notify -> String
showsPrec :: Int -> Notify -> ShowS
$cshowsPrec :: Int -> Notify -> ShowS
Show
{-# LINE 1953 "src/Database/PostgreSQL/LibPQ.hsc" #-}
instance Storable Notify where
sizeOf :: Notify -> Int
sizeOf Notify
_ = (Int
32)
{-# LINE 1955 "src/Database/PostgreSQL/LibPQ.hsc" #-}
alignment :: Notify -> Int
alignment Notify
_ = Int
8
{-# LINE 1957 "src/Database/PostgreSQL/LibPQ.hsc" #-}
peek :: Ptr Notify -> IO Notify
peek Ptr Notify
ptr = do
ByteString
relname <- CString -> IO ByteString
B.packCString (CString -> IO ByteString) -> IO CString -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (\Ptr Notify
hsc_ptr -> Ptr Notify -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Notify
hsc_ptr Int
0) Ptr Notify
ptr
{-# LINE 1960 "src/Database/PostgreSQL/LibPQ.hsc" #-}
extra <- B.packCString =<< (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 1961 "src/Database/PostgreSQL/LibPQ.hsc" #-}
be_pid <- fmap f $ (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 1962 "src/Database/PostgreSQL/LibPQ.hsc" #-}
return $! Notify relname be_pid extra
where
f :: CInt -> CPid
f :: CInt -> CPid
f = CInt -> CPid
forall a b. (Integral a, Num b) => a -> b
fromIntegral
poke :: Ptr Notify -> Notify -> IO ()
poke Ptr Notify
ptr (Notify ByteString
a CPid
b ByteString
c) =
ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
a ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
a' ->
ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
c ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
c' ->
do (\Ptr Notify
hsc_ptr -> Ptr Notify -> Int -> CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Notify
hsc_ptr Int
0) Ptr Notify
ptr CString
a'
{-# LINE 1971 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(\Ptr Notify
hsc_ptr -> Ptr Notify -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Notify
hsc_ptr Int
8) Ptr Notify
ptr (CPid -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral CPid
b :: CInt)
{-# LINE 1972 "src/Database/PostgreSQL/LibPQ.hsc" #-}
(\Ptr Notify
hsc_ptr -> Ptr Notify -> Int -> CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Notify
hsc_ptr Int
16) Ptr Notify
ptr CString
c'
{-# LINE 1973 "src/Database/PostgreSQL/LibPQ.hsc" #-}
notifies :: Connection
-> IO (Maybe Notify)
notifies :: Connection -> IO (Maybe Notify)
notifies Connection
connection =
Connection
-> (Ptr PGconn -> IO (Maybe Notify)) -> IO (Maybe Notify)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Notify)) -> IO (Maybe Notify))
-> (Ptr PGconn -> IO (Maybe Notify)) -> IO (Maybe Notify)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr ->
do Ptr Notify
mn <- Ptr PGconn -> IO (Ptr Notify)
c_PQnotifies Ptr PGconn
ptr
if Ptr Notify
mn Ptr Notify -> Ptr Notify -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Notify
forall a. Ptr a
nullPtr
then Maybe Notify -> IO (Maybe Notify)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Notify
forall a. Maybe a
Nothing
else do
Maybe Notify
result <- Notify -> Maybe Notify
forall a. a -> Maybe a
Just (Notify -> Maybe Notify) -> IO Notify -> IO (Maybe Notify)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr Notify -> IO Notify
forall a. Storable a => Ptr a -> IO a
peek Ptr Notify
mn
Ptr Notify -> IO ()
forall a. Ptr a -> IO ()
c_PQfreemem Ptr Notify
mn
Maybe Notify -> IO (Maybe Notify)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Notify
result
clientEncoding :: Connection
-> IO B.ByteString
clientEncoding :: Connection -> IO ByteString
clientEncoding Connection
connection =
Connection -> (Ptr PGconn -> IO ByteString) -> IO ByteString
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO ByteString) -> IO ByteString)
-> (Ptr PGconn -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr ->
do CInt
i <- Ptr PGconn -> IO CInt
c_PQclientEncoding Ptr PGconn
ptr
CString
cstr <- CInt -> IO CString
c_pg_encoding_to_char CInt
i
CSize
len <- CString -> IO CSize
B.c_strlen CString
cstr
ForeignPtr Word8
fp <- Ptr Word8 -> IO (ForeignPtr Word8)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ (Ptr Word8 -> IO (ForeignPtr Word8))
-> Ptr Word8 -> IO (ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
cstr
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp Int
0 (Int -> ByteString) -> Int -> ByteString
forall a b. (a -> b) -> a -> b
$ CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
len
setClientEncoding :: Connection -> B.ByteString -> IO Bool
setClientEncoding :: Connection -> ByteString -> IO Bool
setClientEncoding Connection
connection ByteString
enc =
do CInt
stat <- Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO CInt)
-> (Ptr PGconn -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
ByteString -> (CString -> IO CInt) -> IO CInt
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
enc ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
s ->
Ptr PGconn -> CString -> IO CInt
c_PQsetClientEncoding Ptr PGconn
c CString
s
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! CInt
stat CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
data Verbosity = ErrorsTerse
| ErrorsDefault
| ErrorsVerbose deriving (Verbosity -> Verbosity -> Bool
(Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool) -> Eq Verbosity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c== :: Verbosity -> Verbosity -> Bool
Eq, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
(Int -> Verbosity -> ShowS)
-> (Verbosity -> String)
-> ([Verbosity] -> ShowS)
-> Show Verbosity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verbosity] -> ShowS
$cshowList :: [Verbosity] -> ShowS
show :: Verbosity -> String
$cshow :: Verbosity -> String
showsPrec :: Int -> Verbosity -> ShowS
$cshowsPrec :: Int -> Verbosity -> ShowS
Show)
instance Enum Verbosity where
toEnum :: Int -> Verbosity
toEnum (Int
0) = Verbosity
ErrorsTerse
{-# LINE 2024 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (1) = ErrorsDefault
{-# LINE 2025 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum (2) = ErrorsVerbose
{-# LINE 2026 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toEnum _ = error "Database.PQ.Enum.Verbosity.toEnum: bad argument"
fromEnum :: Verbosity -> Int
fromEnum Verbosity
ErrorsTerse = (Int
0)
{-# LINE 2029 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum ErrorsDefault = (1)
{-# LINE 2030 "src/Database/PostgreSQL/LibPQ.hsc" #-}
fromEnum ErrorsVerbose = (2)
{-# LINE 2031 "src/Database/PostgreSQL/LibPQ.hsc" #-}
setErrorVerbosity :: Connection
-> Verbosity
-> IO Verbosity
setErrorVerbosity :: Connection -> Verbosity -> IO Verbosity
setErrorVerbosity Connection
connection Verbosity
verbosity =
Connection -> (Ptr PGconn -> IO CInt) -> IO Verbosity
forall a b.
(Integral a, Enum b) =>
Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection ((Ptr PGconn -> IO CInt) -> IO Verbosity)
-> (Ptr PGconn -> IO CInt) -> IO Verbosity
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
p ->
Ptr PGconn -> CInt -> IO CInt
c_PQsetErrorVerbosity Ptr PGconn
p (CInt -> IO CInt) -> CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Verbosity -> Int
forall a. Enum a => a -> Int
fromEnum Verbosity
verbosity
enumFromConn :: (Integral a, Enum b) => Connection
-> (Ptr PGconn -> IO a)
-> IO b
enumFromConn :: Connection -> (Ptr PGconn -> IO a) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO a
f = (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> b
forall a. Enum a => Int -> a
toEnum (Int -> b) -> (a -> Int) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (IO a -> IO b) -> IO a -> IO b
forall a b. (a -> b) -> a -> b
$ Connection -> (Ptr PGconn -> IO a) -> IO a
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO a
f
resultFromConn :: Connection
-> (Ptr PGconn -> IO (Ptr PGresult))
-> IO (Maybe Result)
resultFromConn :: Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Maybe Result)
resultFromConn Connection
connection Ptr PGconn -> IO (Ptr PGresult)
f =
IO (Maybe Result) -> IO (Maybe Result)
forall a. IO a -> IO a
mask_ (IO (Maybe Result) -> IO (Maybe Result))
-> IO (Maybe Result) -> IO (Maybe Result)
forall a b. (a -> b) -> a -> b
$ do
Ptr PGresult
resPtr <- Connection
-> (Ptr PGconn -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO (Ptr PGresult)
f
if Ptr PGresult
resPtr Ptr PGresult -> Ptr PGresult -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGresult
forall a. Ptr a
nullPtr
then Maybe Result -> IO (Maybe Result)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Result
forall a. Maybe a
Nothing
else (Result -> Maybe Result
forall a. a -> Maybe a
Just (Result -> Maybe Result)
-> (ForeignPtr PGresult -> Result)
-> ForeignPtr PGresult
-> Maybe Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr PGresult -> Result
Result) (ForeignPtr PGresult -> Maybe Result)
-> IO (ForeignPtr PGresult) -> IO (Maybe Result)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` FinalizerPtr PGresult -> Ptr PGresult -> IO (ForeignPtr PGresult)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr PGresult
p_PQclear Ptr PGresult
resPtr
withResult :: Result
-> (Ptr PGresult -> IO b)
-> IO b
withResult :: Result -> (Ptr PGresult -> IO b) -> IO b
withResult (Result ForeignPtr PGresult
fp) Ptr PGresult -> IO b
f = ForeignPtr PGresult -> (Ptr PGresult -> IO b) -> IO b
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr PGresult
fp Ptr PGresult -> IO b
f
numFromResult :: (Integral a, Num b) => Result
-> (Ptr PGresult -> IO a)
-> IO b
numFromResult :: Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result Ptr PGresult -> IO a
f = (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO a -> IO b) -> IO a -> IO b
forall a b. (a -> b) -> a -> b
$ Result -> (Ptr PGresult -> IO a) -> IO a
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result Ptr PGresult -> IO a
f
enumFromResult :: (Integral a, Enum b) => Result
-> (Ptr PGresult -> IO a)
-> IO b
enumFromResult :: Result -> (Ptr PGresult -> IO a) -> IO b
enumFromResult Result
result Ptr PGresult -> IO a
f = (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> b
forall a. Enum a => Int -> a
toEnum (Int -> b) -> (a -> Int) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (IO a -> IO b) -> IO a -> IO b
forall a b. (a -> b) -> a -> b
$ Result -> (Ptr PGresult -> IO a) -> IO a
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result Ptr PGresult -> IO a
f
maybeBsFromResult :: Result
-> (Ptr PGresult -> IO CString)
-> IO (Maybe B.ByteString)
maybeBsFromResult :: Result -> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
maybeBsFromResult (Result ForeignPtr PGresult
res) Ptr PGresult -> IO CString
f = ForeignPtr PGresult
-> (Ptr PGresult -> IO CString) -> IO (Maybe ByteString)
forall a.
ForeignPtr a -> (Ptr a -> IO CString) -> IO (Maybe ByteString)
maybeBsFromForeignPtr ForeignPtr PGresult
res Ptr PGresult -> IO CString
f
maybeBsFromForeignPtr :: ForeignPtr a
-> (Ptr a -> IO CString)
-> IO (Maybe B.ByteString)
maybeBsFromForeignPtr :: ForeignPtr a -> (Ptr a -> IO CString) -> IO (Maybe ByteString)
maybeBsFromForeignPtr ForeignPtr a
fp Ptr a -> IO CString
f =
ForeignPtr a
-> (Ptr a -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr a
fp ((Ptr a -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr a -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr a
p ->
do CString
cstr <- Ptr a -> IO CString
f Ptr a
p
if CString
cstr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do Int
l <- CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int) -> IO CSize -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CString -> IO CSize
B.c_strlen CString
cstr
ForeignPtr Word8
fp' <- Ptr Word8 -> IO () -> IO (ForeignPtr Word8)
forall a. Ptr a -> IO () -> IO (ForeignPtr a)
FC.newForeignPtr (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
cstr) IO ()
finalizer
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp' Int
0 Int
l
where
finalizer :: IO ()
finalizer = ForeignPtr a -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr a
fp
type NoticeReceiver = NoticeBuffer -> Ptr PGresult -> IO ()
data PGnotice
disableNoticeReporting :: Connection -> IO ()
disableNoticeReporting :: Connection -> IO ()
disableNoticeReporting conn :: Connection
conn@(Conn ForeignPtr PGconn
_ MVar (Ptr CNoticeBuffer)
nbRef) = do
FunPtr NoticeReceiver
_ <- Connection
-> (Ptr PGconn -> IO (FunPtr NoticeReceiver))
-> IO (FunPtr NoticeReceiver)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn ((Ptr PGconn -> IO (FunPtr NoticeReceiver))
-> IO (FunPtr NoticeReceiver))
-> (Ptr PGconn -> IO (FunPtr NoticeReceiver))
-> IO (FunPtr NoticeReceiver)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> Ptr PGconn
-> FunPtr NoticeReceiver
-> Ptr CNoticeBuffer
-> IO (FunPtr NoticeReceiver)
c_PQsetNoticeReceiver Ptr PGconn
c FunPtr NoticeReceiver
p_discard_notices Ptr CNoticeBuffer
forall a. Ptr a
nullPtr
Ptr CNoticeBuffer
nb <- MVar (Ptr CNoticeBuffer)
-> Ptr CNoticeBuffer -> IO (Ptr CNoticeBuffer)
forall a. MVar a -> a -> IO a
swapMVar MVar (Ptr CNoticeBuffer)
nbRef Ptr CNoticeBuffer
forall a. Ptr a
nullPtr
Ptr CNoticeBuffer -> IO ()
c_free_noticebuffer Ptr CNoticeBuffer
nb
enableNoticeReporting :: Connection -> IO ()
enableNoticeReporting :: Connection -> IO ()
enableNoticeReporting conn :: Connection
conn@(Conn ForeignPtr PGconn
_ MVar (Ptr CNoticeBuffer)
nbRef) = do
if Connection -> Bool
isNullConnection Connection
conn
then () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
Ptr CNoticeBuffer
nb' <- IO (Ptr CNoticeBuffer)
c_malloc_noticebuffer
FunPtr NoticeReceiver
_ <- Connection
-> (Ptr PGconn -> IO (FunPtr NoticeReceiver))
-> IO (FunPtr NoticeReceiver)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn ((Ptr PGconn -> IO (FunPtr NoticeReceiver))
-> IO (FunPtr NoticeReceiver))
-> (Ptr PGconn -> IO (FunPtr NoticeReceiver))
-> IO (FunPtr NoticeReceiver)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> Ptr PGconn
-> FunPtr NoticeReceiver
-> Ptr CNoticeBuffer
-> IO (FunPtr NoticeReceiver)
c_PQsetNoticeReceiver Ptr PGconn
c FunPtr NoticeReceiver
p_store_notices Ptr CNoticeBuffer
nb'
Ptr CNoticeBuffer
nb <- MVar (Ptr CNoticeBuffer)
-> Ptr CNoticeBuffer -> IO (Ptr CNoticeBuffer)
forall a. MVar a -> a -> IO a
swapMVar MVar (Ptr CNoticeBuffer)
nbRef Ptr CNoticeBuffer
nb'
Ptr CNoticeBuffer -> IO ()
c_free_noticebuffer Ptr CNoticeBuffer
nb
getNotice :: Connection -> IO (Maybe B.ByteString)
getNotice :: Connection -> IO (Maybe ByteString)
getNotice (Conn ForeignPtr PGconn
_ MVar (Ptr CNoticeBuffer)
nbRef) =
MVar (Ptr CNoticeBuffer)
-> (Ptr CNoticeBuffer -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar (Ptr CNoticeBuffer)
nbRef ((Ptr CNoticeBuffer -> IO (Maybe ByteString))
-> IO (Maybe ByteString))
-> (Ptr CNoticeBuffer -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CNoticeBuffer
nb -> do
Ptr PGnotice
np <- Ptr CNoticeBuffer -> IO (Ptr PGnotice)
c_get_notice Ptr CNoticeBuffer
nb
if Ptr PGnotice
np Ptr PGnotice -> Ptr PGnotice -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGnotice
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do
ForeignPtr Word8
fp <- FinalizerPtr Word8 -> Ptr Word8 -> IO (ForeignPtr Word8)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Word8
forall a. FunPtr (Ptr a -> IO ())
finalizerFree (Ptr PGnotice -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr PGnotice
np)
Int
len <- (\Ptr PGnotice
hsc_ptr -> Ptr PGnotice -> Int -> IO Int
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr PGnotice
hsc_ptr Int
8) Ptr PGnotice
np
{-# LINE 2173 "src/Database/PostgreSQL/LibPQ.hsc" #-}
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
mkPS ForeignPtr Word8
fp ((Int
16)) Int
len
{-# LINE 2174 "src/Database/PostgreSQL/LibPQ.hsc" #-}
newtype LoFd = LoFd CInt deriving (LoFd -> LoFd -> Bool
(LoFd -> LoFd -> Bool) -> (LoFd -> LoFd -> Bool) -> Eq LoFd
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LoFd -> LoFd -> Bool
$c/= :: LoFd -> LoFd -> Bool
== :: LoFd -> LoFd -> Bool
$c== :: LoFd -> LoFd -> Bool
Eq, Eq LoFd
Eq LoFd
-> (LoFd -> LoFd -> Ordering)
-> (LoFd -> LoFd -> Bool)
-> (LoFd -> LoFd -> Bool)
-> (LoFd -> LoFd -> Bool)
-> (LoFd -> LoFd -> Bool)
-> (LoFd -> LoFd -> LoFd)
-> (LoFd -> LoFd -> LoFd)
-> Ord LoFd
LoFd -> LoFd -> Bool
LoFd -> LoFd -> Ordering
LoFd -> LoFd -> LoFd
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LoFd -> LoFd -> LoFd
$cmin :: LoFd -> LoFd -> LoFd
max :: LoFd -> LoFd -> LoFd
$cmax :: LoFd -> LoFd -> LoFd
>= :: LoFd -> LoFd -> Bool
$c>= :: LoFd -> LoFd -> Bool
> :: LoFd -> LoFd -> Bool
$c> :: LoFd -> LoFd -> Bool
<= :: LoFd -> LoFd -> Bool
$c<= :: LoFd -> LoFd -> Bool
< :: LoFd -> LoFd -> Bool
$c< :: LoFd -> LoFd -> Bool
compare :: LoFd -> LoFd -> Ordering
$ccompare :: LoFd -> LoFd -> Ordering
$cp1Ord :: Eq LoFd
Ord, Int -> LoFd -> ShowS
[LoFd] -> ShowS
LoFd -> String
(Int -> LoFd -> ShowS)
-> (LoFd -> String) -> ([LoFd] -> ShowS) -> Show LoFd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LoFd] -> ShowS
$cshowList :: [LoFd] -> ShowS
show :: LoFd -> String
$cshow :: LoFd -> String
showsPrec :: Int -> LoFd -> ShowS
$cshowsPrec :: Int -> LoFd -> ShowS
Show)
loMode :: IOMode -> CInt
loMode :: IOMode -> CInt
loMode IOMode
mode = case IOMode
mode of
IOMode
ReadMode -> (CInt
262144)
{-# LINE 2185 "src/Database/PostgreSQL/LibPQ.hsc" #-}
IOMode
WriteMode -> (CInt
131072)
{-# LINE 2186 "src/Database/PostgreSQL/LibPQ.hsc" #-}
IOMode
ReadWriteMode -> (CInt
262144) CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. (CInt
131072)
{-# LINE 2187 "src/Database/PostgreSQL/LibPQ.hsc" #-}
IOMode
AppendMode -> (CInt
131072)
{-# LINE 2188 "src/Database/PostgreSQL/LibPQ.hsc" #-}
toMaybeOid :: Oid -> IO (Maybe Oid)
toMaybeOid :: Oid -> IO (Maybe Oid)
toMaybeOid Oid
oid | Oid
oid Oid -> Oid -> Bool
forall a. Eq a => a -> a -> Bool
== Oid
invalidOid = Maybe Oid -> IO (Maybe Oid)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Oid
forall a. Maybe a
Nothing
| Bool
otherwise = Maybe Oid -> IO (Maybe Oid)
forall (m :: * -> *) a. Monad m => a -> m a
return (Oid -> Maybe Oid
forall a. a -> Maybe a
Just Oid
oid)
{-# INLINE toMaybeOid #-}
nonnegInt :: CInt -> IO (Maybe Int)
nonnegInt :: CInt -> IO (Maybe Int)
nonnegInt CInt
x = if CInt
x CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0 then Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing else Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Maybe Int
forall a. a -> Maybe a
Just (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x))
{-# INLINE nonnegInt #-}
negError :: CInt -> IO (Maybe ())
negError :: CInt -> IO (Maybe ())
negError CInt
x = if CInt
x CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0 then Maybe () -> IO (Maybe ())
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ()
forall a. Maybe a
Nothing else Maybe () -> IO (Maybe ())
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> Maybe ()
forall a. a -> Maybe a
Just ())
{-# INLINE negError #-}
loCreat :: Connection -> IO (Maybe Oid)
loCreat :: Connection -> IO (Maybe Oid)
loCreat Connection
connection
= Connection -> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid))
-> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
Oid -> IO (Maybe Oid)
toMaybeOid (Oid -> IO (Maybe Oid)) -> IO Oid -> IO (Maybe Oid)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CInt -> IO Oid
c_lo_creat Ptr PGconn
c (IOMode -> CInt
loMode IOMode
ReadMode)
loCreate :: Connection -> Oid -> IO (Maybe Oid)
loCreate :: Connection -> Oid -> IO (Maybe Oid)
loCreate Connection
connection Oid
oid
= Connection -> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid))
-> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
Oid -> IO (Maybe Oid)
toMaybeOid (Oid -> IO (Maybe Oid)) -> IO Oid -> IO (Maybe Oid)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> Oid -> IO Oid
c_lo_create Ptr PGconn
c Oid
oid
loImport :: Connection -> FilePath -> IO (Maybe Oid)
loImport :: Connection -> String -> IO (Maybe Oid)
loImport Connection
connection String
filepath
= Connection -> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid))
-> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
String -> (CString -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a. String -> (CString -> IO a) -> IO a
withCString String
filepath ((CString -> IO (Maybe Oid)) -> IO (Maybe Oid))
-> (CString -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a b. (a -> b) -> a -> b
$ \CString
f -> do
Oid -> IO (Maybe Oid)
toMaybeOid (Oid -> IO (Maybe Oid)) -> IO Oid -> IO (Maybe Oid)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CString -> IO Oid
c_lo_import Ptr PGconn
c CString
f
loImportWithOid :: Connection -> FilePath -> Oid -> IO (Maybe Oid)
loImportWithOid :: Connection -> String -> Oid -> IO (Maybe Oid)
loImportWithOid Connection
connection String
filepath Oid
oid
= Connection -> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid))
-> (Ptr PGconn -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
String -> (CString -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a. String -> (CString -> IO a) -> IO a
withCString String
filepath ((CString -> IO (Maybe Oid)) -> IO (Maybe Oid))
-> (CString -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a b. (a -> b) -> a -> b
$ \CString
f -> do
Oid -> IO (Maybe Oid)
toMaybeOid (Oid -> IO (Maybe Oid)) -> IO Oid -> IO (Maybe Oid)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CString -> Oid -> IO Oid
c_lo_import_with_oid Ptr PGconn
c CString
f Oid
oid
loExport :: Connection -> Oid -> FilePath -> IO (Maybe ())
loExport :: Connection -> Oid -> String -> IO (Maybe ())
loExport Connection
connection Oid
oid String
filepath
= Connection -> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ()))
-> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
String -> (CString -> IO (Maybe ())) -> IO (Maybe ())
forall a. String -> (CString -> IO a) -> IO a
withCString String
filepath ((CString -> IO (Maybe ())) -> IO (Maybe ()))
-> (CString -> IO (Maybe ())) -> IO (Maybe ())
forall a b. (a -> b) -> a -> b
$ \CString
f -> do
CInt -> IO (Maybe ())
negError (CInt -> IO (Maybe ())) -> IO CInt -> IO (Maybe ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> Oid -> CString -> IO CInt
c_lo_export Ptr PGconn
c Oid
oid CString
f
loOpen :: Connection -> Oid -> IOMode -> IO (Maybe LoFd)
loOpen :: Connection -> Oid -> IOMode -> IO (Maybe LoFd)
loOpen Connection
connection Oid
oid IOMode
mode
= Connection -> (Ptr PGconn -> IO (Maybe LoFd)) -> IO (Maybe LoFd)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe LoFd)) -> IO (Maybe LoFd))
-> (Ptr PGconn -> IO (Maybe LoFd)) -> IO (Maybe LoFd)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt
fd <- Ptr PGconn -> Oid -> CInt -> IO CInt
c_lo_open Ptr PGconn
c Oid
oid (IOMode -> CInt
loMode IOMode
mode)
case CInt
fd of
-1 -> Maybe LoFd -> IO (Maybe LoFd)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LoFd
forall a. Maybe a
Nothing
CInt
_ | IOMode
mode IOMode -> IOMode -> Bool
forall a. Eq a => a -> a -> Bool
/= IOMode
AppendMode -> Maybe LoFd -> IO (Maybe LoFd)
forall (m :: * -> *) a. Monad m => a -> m a
return (LoFd -> Maybe LoFd
forall a. a -> Maybe a
Just (CInt -> LoFd
LoFd CInt
fd))
| Bool
otherwise -> do
CInt
err <- Ptr PGconn -> CInt -> CInt -> CInt -> IO CInt
c_lo_lseek Ptr PGconn
c CInt
fd CInt
0 (CInt
2)
{-# LINE 2286 "src/Database/PostgreSQL/LibPQ.hsc" #-}
case CInt
err of
-1 -> do
CInt
_ <- Ptr PGconn -> CInt -> IO CInt
c_lo_close Ptr PGconn
c CInt
fd
Maybe LoFd -> IO (Maybe LoFd)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LoFd
forall a. Maybe a
Nothing
CInt
_ -> Maybe LoFd -> IO (Maybe LoFd)
forall (m :: * -> *) a. Monad m => a -> m a
return (LoFd -> Maybe LoFd
forall a. a -> Maybe a
Just (CInt -> LoFd
LoFd CInt
fd))
loWrite :: Connection -> LoFd -> B.ByteString -> IO (Maybe Int)
loWrite :: Connection -> LoFd -> ByteString -> IO (Maybe Int)
loWrite Connection
connection (LoFd CInt
fd) ByteString
bytes
= Connection -> (Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int))
-> (Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
ByteString -> (CStringLen -> IO (Maybe Int)) -> IO (Maybe Int)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bytes ((CStringLen -> IO (Maybe Int)) -> IO (Maybe Int))
-> (CStringLen -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \(CString
byteptr,Int
len) -> do
CInt -> IO (Maybe Int)
nonnegInt (CInt -> IO (Maybe Int)) -> IO CInt -> IO (Maybe Int)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CInt -> CString -> CSize -> IO CInt
c_lo_write Ptr PGconn
c CInt
fd CString
byteptr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
loRead :: Connection -> LoFd -> Int -> IO (Maybe B.ByteString)
loRead :: Connection -> LoFd -> Int -> IO (Maybe ByteString)
loRead Connection
connection (LoFd !CInt
fd) !Int
maxlen
= Connection
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr PGconn -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
Ptr Word8
buf <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
maxlen
CInt
len_ <- Ptr PGconn -> CInt -> Ptr Word8 -> CSize -> IO CInt
c_lo_read Ptr PGconn
c CInt
fd Ptr Word8
buf (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxlen)
let len :: Int
len = CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len_
if Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
then do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
buf
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do
Ptr Word8
bufre <- Ptr Word8 -> Int -> IO (Ptr Word8)
forall a. Ptr a -> Int -> IO (Ptr a)
reallocBytes Ptr Word8
buf Int
len
ForeignPtr Word8
buffp <- FinalizerPtr Word8 -> Ptr Word8 -> IO (ForeignPtr Word8)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Word8
forall a. FunPtr (Ptr a -> IO ())
finalizerFree Ptr Word8
bufre
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
buffp Int
0 Int
len
loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO (Maybe Int)
loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO (Maybe Int)
loSeek Connection
connection (LoFd CInt
fd) SeekMode
seekmode Int
delta
= Connection -> (Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int))
-> (Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
let d :: CInt
d = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
delta
CInt
pos <- Ptr PGconn -> CInt -> CInt -> CInt -> IO CInt
c_lo_lseek Ptr PGconn
c CInt
fd CInt
d (CInt -> IO CInt) -> CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ case SeekMode
seekmode of
SeekMode
AbsoluteSeek -> CInt
0
{-# LINE 2335 "src/Database/PostgreSQL/LibPQ.hsc" #-}
SeekMode
RelativeSeek -> CInt
1
{-# LINE 2336 "src/Database/PostgreSQL/LibPQ.hsc" #-}
SeekMode
SeekFromEnd -> CInt
2
{-# LINE 2337 "src/Database/PostgreSQL/LibPQ.hsc" #-}
CInt -> IO (Maybe Int)
nonnegInt CInt
pos
loTell :: Connection -> LoFd -> IO (Maybe Int)
loTell :: Connection -> LoFd -> IO (Maybe Int)
loTell Connection
connection (LoFd CInt
fd)
= Connection -> (Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int)
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int))
-> (Ptr PGconn -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe Int)
nonnegInt (CInt -> IO (Maybe Int)) -> IO CInt -> IO (Maybe Int)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CInt -> IO CInt
c_lo_tell Ptr PGconn
c CInt
fd
loTruncate :: Connection -> LoFd -> Int -> IO (Maybe ())
loTruncate :: Connection -> LoFd -> Int -> IO (Maybe ())
loTruncate Connection
connection (LoFd CInt
fd) Int
size
= Connection -> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ()))
-> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe ())
negError (CInt -> IO (Maybe ())) -> IO CInt -> IO (Maybe ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CInt -> CSize -> IO CInt
c_lo_truncate Ptr PGconn
c CInt
fd (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
loClose :: Connection -> LoFd -> IO (Maybe ())
loClose :: Connection -> LoFd -> IO (Maybe ())
loClose Connection
connection (LoFd CInt
fd)
= Connection -> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ()))
-> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe ())
negError (CInt -> IO (Maybe ())) -> IO CInt -> IO (Maybe ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> CInt -> IO CInt
c_lo_close Ptr PGconn
c CInt
fd
loUnlink :: Connection -> Oid -> IO (Maybe ())
loUnlink :: Connection -> Oid -> IO (Maybe ())
loUnlink Connection
connection Oid
oid
= Connection -> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection ((Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ()))
-> (Ptr PGconn -> IO (Maybe ())) -> IO (Maybe ())
forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe ())
negError (CInt -> IO (Maybe ())) -> IO CInt -> IO (Maybe ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr PGconn -> Oid -> IO CInt
c_lo_unlink Ptr PGconn
c Oid
oid
foreign import ccall "libpq-fe.h PQconnectdb"
c_PQconnectdb :: CString ->IO (Ptr PGconn)
foreign import ccall "libpq-fe.h PQconnectStart"
c_PQconnectStart :: CString ->IO (Ptr PGconn)
foreign import ccall "libpq-fe.h PQconnectPoll"
c_PQconnectPoll :: Ptr PGconn ->IO CInt
foreign import ccall unsafe "libpq-fe.h PQdb"
c_PQdb :: Ptr PGconn -> IO CString
foreign import ccall unsafe "libpq-fe.h PQuser"
c_PQuser :: Ptr PGconn -> IO CString
foreign import ccall unsafe "libpq-fe.h PQpass"
c_PQpass :: Ptr PGconn -> IO CString
foreign import ccall unsafe "libpq-fe.h PQhost"
c_PQhost :: Ptr PGconn -> IO CString
foreign import ccall unsafe "libpq-fe.h PQport"
c_PQport :: Ptr PGconn -> IO CString
foreign import ccall unsafe "libpq-fe.h PQoptions"
c_PQoptions :: Ptr PGconn -> IO CString
foreign import ccall unsafe "libpq-fe.h PQbackendPID"
c_PQbackendPID :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQconnectionNeedsPassword"
c_PQconnectionNeedsPassword :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQconnectionUsedPassword"
c_PQconnectionUsedPassword :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQstatus"
c_PQstatus :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQtransactionStatus"
c_PQtransactionStatus :: Ptr PGconn -> IO CInt
foreign import ccall "libpq-fe.h PQparameterStatus"
c_PQparameterStatus :: Ptr PGconn -> CString -> IO CString
foreign import ccall unsafe "libpq-fe.h PQprotocolVersion"
c_PQprotocolVersion :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQserverVersion"
c_PQserverVersion :: Ptr PGconn -> IO CInt
foreign import ccall "dynamic"
mkLibpqVersion :: FunPtr Int -> Int
foreign import ccall unsafe "libpq-fe.h PQsocket"
c_PQsocket :: Ptr PGconn -> IO CInt
foreign import ccall "libpq-fe.h PQerrorMessage"
c_PQerrorMessage :: Ptr PGconn -> IO CString
{-# LINE 2438 "src/Database/PostgreSQL/LibPQ.hsc" #-}
foreign import ccall "libpq-fe.h PQfinish"
c_PQfinish :: Ptr PGconn -> IO ()
{-# LINE 2444 "src/Database/PostgreSQL/LibPQ.hsc" #-}
foreign import ccall "libpq-fe.h PQreset"
c_PQreset :: Ptr PGconn -> IO ()
foreign import ccall "libpq-fe.h PQresetStart"
c_PQresetStart :: Ptr PGconn ->IO CInt
foreign import ccall "libpq-fe.h PQresetPoll"
c_PQresetPoll :: Ptr PGconn ->IO CInt
foreign import ccall unsafe "libpq-fe.h PQclientEncoding"
c_PQclientEncoding :: Ptr PGconn -> IO CInt
foreign import ccall "libpq-fe.h pg_encoding_to_char"
c_pg_encoding_to_char :: CInt -> IO CString
foreign import ccall "libpq-fe.h PQsetClientEncoding"
c_PQsetClientEncoding :: Ptr PGconn -> CString -> IO CInt
type PGVerbosity = CInt
foreign import ccall unsafe "libpq-fe.h PQsetErrorVerbosity"
c_PQsetErrorVerbosity :: Ptr PGconn -> PGVerbosity -> IO PGVerbosity
foreign import ccall "libpq-fe.h PQputCopyData"
c_PQputCopyData :: Ptr PGconn -> Ptr CChar -> CInt -> IO CInt
foreign import ccall "libpq-fe.h PQputCopyEnd"
c_PQputCopyEnd :: Ptr PGconn -> CString -> IO CInt
foreign import ccall "libpq-fe.h PQgetCopyData"
c_PQgetCopyData :: Ptr PGconn -> Ptr (Ptr Word8) -> CInt -> IO CInt
foreign import ccall "libpq-fe.h PQsendQuery"
c_PQsendQuery :: Ptr PGconn -> CString ->IO CInt
foreign import ccall "libpq-fe.h PQsendQueryParams"
c_PQsendQueryParams :: Ptr PGconn -> CString -> CInt -> Ptr Oid
-> Ptr CString -> Ptr CInt -> Ptr CInt -> CInt
-> IO CInt
foreign import ccall "libpq-fe.h PQsendPrepare"
c_PQsendPrepare :: Ptr PGconn -> CString -> CString -> CInt -> Ptr Oid
-> IO CInt
foreign import ccall "libpq-fe.h PQsendQueryPrepared"
c_PQsendQueryPrepared :: Ptr PGconn -> CString -> CInt -> Ptr CString
-> Ptr CInt -> Ptr CInt -> CInt -> IO CInt
foreign import ccall "libpq-fe.h PQsendDescribePrepared"
c_PQsendDescribePrepared :: Ptr PGconn -> CString -> IO CInt
foreign import ccall "libpq-fe.h PQsendDescribePortal"
c_PQsendDescribePortal :: Ptr PGconn -> CString -> IO CInt
foreign import ccall "libpq-fe.h PQflush"
c_PQflush :: Ptr PGconn -> IO CInt
foreign import ccall "libpq-fe.h PQgetCancel"
c_PQgetCancel :: Ptr PGconn -> IO (Ptr PGcancel)
foreign import ccall "libpq-fe.h &PQfreeCancel"
p_PQfreeCancel :: FunPtr (Ptr PGcancel -> IO ())
foreign import ccall "libpq-fe.h PQcancel"
c_PQcancel :: Ptr PGcancel -> CString -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQnotifies"
c_PQnotifies :: Ptr PGconn -> IO (Ptr Notify)
foreign import ccall "libpq-fe.h PQconsumeInput"
c_PQconsumeInput :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQisBusy"
c_PQisBusy :: Ptr PGconn -> IO CInt
foreign import ccall "libpq-fe.h PQsetnonblocking"
c_PQsetnonblocking :: Ptr PGconn -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQisnonblocking"
c_PQisnonblocking :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQsetSingleRowMode"
c_PQsetSingleRowMode :: Ptr PGconn -> IO CInt
foreign import ccall "libpq-fe.h PQgetResult"
c_PQgetResult :: Ptr PGconn -> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h PQexec"
c_PQexec :: Ptr PGconn -> CString -> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h PQexecParams"
c_PQexecParams :: Ptr PGconn -> CString -> CInt -> Ptr Oid
-> Ptr CString -> Ptr CInt -> Ptr CInt -> CInt
-> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h PQprepare"
c_PQprepare :: Ptr PGconn -> CString -> CString -> CInt -> Ptr Oid
-> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h PQexecPrepared"
c_PQexecPrepared :: Ptr PGconn -> CString -> CInt -> Ptr CString
-> Ptr CInt -> Ptr CInt -> CInt -> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h PQdescribePrepared"
c_PQdescribePrepared :: Ptr PGconn -> CString -> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h PQdescribePortal"
c_PQdescribePortal :: Ptr PGconn -> CString -> IO (Ptr PGresult)
foreign import ccall "libpq-fe.h &PQclear"
p_PQclear :: FunPtr (Ptr PGresult ->IO ())
foreign import ccall unsafe "libpq-fe.h PQresultStatus"
c_PQresultStatus :: Ptr PGresult -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQresStatus"
c_PQresStatus :: CInt -> IO CString
foreign import ccall unsafe "libpq-fe.h PQresultErrorMessage"
c_PQresultErrorMessage :: Ptr PGresult -> IO CString
foreign import ccall "libpq-fe.h PQresultErrorField"
c_PQresultErrorField :: Ptr PGresult -> CInt -> IO CString
foreign import ccall unsafe "libpq-fe.h PQntuples"
c_PQntuples :: Ptr PGresult -> CInt
foreign import ccall unsafe "libpq-fe.h PQnfields"
c_PQnfields :: Ptr PGresult -> CInt
foreign import ccall unsafe "libpq-fe.h PQfname"
c_PQfname :: Ptr PGresult -> CInt -> IO CString
foreign import ccall unsafe "libpq-fe.h PQfnumber"
c_PQfnumber :: Ptr PGresult -> CString -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQftable"
c_PQftable :: Ptr PGresult -> CInt -> IO Oid
foreign import ccall unsafe "libpq-fe.h PQftablecol"
c_PQftablecol :: Ptr PGresult -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQfformat"
c_PQfformat :: Ptr PGresult -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQftype"
c_PQftype :: Ptr PGresult -> CInt -> IO Oid
foreign import ccall unsafe "libpq-fe.h PQfmod"
c_PQfmod :: Ptr PGresult -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQfsize"
c_PQfsize :: Ptr PGresult -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQgetvalue"
c_PQgetvalue :: Ptr PGresult -> CInt -> CInt -> IO CString
foreign import ccall unsafe "libpq-fe.h PQgetisnull"
c_PQgetisnull :: Ptr PGresult -> CInt -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQgetlength"
c_PQgetlength :: Ptr PGresult -> CInt -> CInt -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQnparams"
c_PQnparams :: Ptr PGresult -> IO CInt
foreign import ccall unsafe "libpq-fe.h PQparamtype"
c_PQparamtype :: Ptr PGresult -> CInt -> IO Oid
foreign import ccall unsafe "libpq-fe.h PQcmdStatus"
c_PQcmdStatus :: Ptr PGresult -> IO CString
foreign import ccall unsafe "libpq-fe.h PQcmdTuples"
c_PQcmdTuples :: Ptr PGresult -> IO CString
foreign import ccall "libpq-fe.h PQescapeStringConn"
c_PQescapeStringConn :: Ptr PGconn
-> Ptr Word8
-> CString
-> CSize
-> Ptr CInt
-> IO CSize
foreign import ccall "libpq-fe.h PQescapeByteaConn"
c_PQescapeByteaConn :: Ptr PGconn
-> CString
-> CSize
-> Ptr CSize
-> IO (Ptr Word8)
foreign import ccall "libpq-fe.h PQunescapeBytea"
c_PQunescapeBytea :: CString
-> Ptr CSize
-> IO (Ptr Word8)
foreign import ccall unsafe "libpq-fe.h PQescapeIdentifier"
c_PQescapeIdentifier :: Ptr PGconn
-> CString
-> CSize
-> IO CString
foreign import ccall unsafe "libpq-fe.h &PQfreemem"
p_PQfreemem :: FunPtr (Ptr a -> IO ())
foreign import ccall unsafe "libpq-fe.h PQfreemem"
c_PQfreemem :: Ptr a -> IO ()
foreign import ccall unsafe "noticehandlers.h hs_postgresql_libpq_malloc_noticebuffer"
c_malloc_noticebuffer :: IO (Ptr CNoticeBuffer)
foreign import ccall unsafe "noticehandlers.h hs_postgresql_libpq_free_noticebuffer"
c_free_noticebuffer :: Ptr CNoticeBuffer -> IO ()
foreign import ccall unsafe "noticehandlers.h hs_postgresql_libpq_get_notice"
c_get_notice :: Ptr CNoticeBuffer -> IO (Ptr PGnotice)
foreign import ccall unsafe "noticehandlers.h &hs_postgresql_libpq_discard_notices"
p_discard_notices :: FunPtr NoticeReceiver
foreign import ccall unsafe "noticehandlers.h &hs_postgresql_libpq_store_notices"
p_store_notices :: FunPtr NoticeReceiver
foreign import ccall unsafe "libpq-fe.h PQsetNoticeReceiver"
c_PQsetNoticeReceiver :: Ptr PGconn -> FunPtr NoticeReceiver -> Ptr CNoticeBuffer -> IO (FunPtr NoticeReceiver)
type CFd = CInt
foreign import ccall "libpq-fs.h lo_creat"
c_lo_creat :: Ptr PGconn -> CInt -> IO Oid
foreign import ccall "libpq-fs.h lo_create"
c_lo_create :: Ptr PGconn -> Oid -> IO Oid
foreign import ccall "libpq-fs.h lo_import"
c_lo_import :: Ptr PGconn -> CString -> IO Oid
foreign import ccall "libpq-fs.h lo_import_with_oid"
c_lo_import_with_oid :: Ptr PGconn -> CString -> Oid -> IO Oid
foreign import ccall "libpq-fs.h lo_export"
c_lo_export :: Ptr PGconn -> Oid -> CString -> IO CInt
foreign import ccall "libpq-fs.h lo_open"
c_lo_open :: Ptr PGconn -> Oid -> CInt -> IO CFd
foreign import ccall "libpq-fs.h lo_write"
c_lo_write :: Ptr PGconn -> CFd -> CString -> CSize -> IO CInt
foreign import ccall "libpq-fs.h lo_read"
c_lo_read :: Ptr PGconn -> CFd -> Ptr Word8 -> CSize -> IO CInt
foreign import ccall "libpq-fs.h lo_lseek"
c_lo_lseek :: Ptr PGconn -> CFd -> CInt -> CInt -> IO CInt
foreign import ccall "libpq-fs.h lo_tell"
c_lo_tell :: Ptr PGconn -> CFd -> IO CInt
foreign import ccall "libpq-fs.h lo_truncate"
c_lo_truncate :: Ptr PGconn -> CFd -> CSize -> IO CInt
foreign import ccall "libpq-fs.h lo_close"
c_lo_close :: Ptr PGconn -> CFd -> IO CInt
foreign import ccall "libpq-fs.h lo_unlink"
c_lo_unlink :: Ptr PGconn -> Oid -> IO CInt