{-# LANGUAGE BangPatterns               #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE NoForeignFunctionInterface #-}
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 Control.Concurrent.MVar (MVar, newMVar, swapMVar, tryTakeMVar, withMVar)
import Control.Exception       (mask_)
import Foreign.C.String        (CString, CStringLen, withCString)
import Foreign.C.Types         (CInt (..))
import Foreign.ForeignPtr      (ForeignPtr, finalizeForeignPtr, newForeignPtr, newForeignPtr_, touchForeignPtr, withForeignPtr)
import Foreign.Marshal         (alloca, allocaBytes, finalizerFree, free, mallocBytes, maybeWith, reallocBytes, withArrayLen, withMany)
import Foreign.Ptr             (Ptr, castPtr, nullPtr)
import Foreign.Storable        (Storable (peek))
import GHC.Conc                (closeFdWith)
import System.IO               (IOMode (..), SeekMode (..))
import System.Posix.Types      (CPid, Fd (..))
import qualified Data.ByteString           as B
import qualified Data.ByteString.Internal  as B (c_strlen, createAndTrim, fromForeignPtr)
import qualified Data.ByteString.Unsafe    as B
import qualified Foreign.Concurrent        as FC
import qualified Foreign.ForeignPtr.Unsafe as Unsafe
import Database.PostgreSQL.LibPQ.Compat
import Database.PostgreSQL.LibPQ.Enums
import Database.PostgreSQL.LibPQ.FFI
import Database.PostgreSQL.LibPQ.Internal
import Database.PostgreSQL.LibPQ.Marshal
import Database.PostgreSQL.LibPQ.Notify
import Database.PostgreSQL.LibPQ.Oid
import Database.PostgreSQL.LibPQ.Ptr
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 [Char] -> IO Connection
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"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 a. a -> IO a
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 [Char] -> IO Connection
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"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 a. a -> IO a
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
   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)
   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 :: forall a. 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 a b. IO a -> (a -> IO b) -> IO b
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 a. a -> IO a
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 a. a -> IO a
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
isNullConnection :: Connection -> Bool
isNullConnection (Conn ForeignPtr PGconn
x MVar (Ptr CNoticeBuffer)
_) = ForeignPtr PGconn -> Ptr PGconn
forall a. ForeignPtr a -> Ptr a
Unsafe.unsafeForeignPtrToPtr ForeignPtr PGconn
x Ptr PGconn -> Ptr PGconn -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PGconn
forall a. Ptr a
nullPtr
{-# 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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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
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
       IO PollingStatus
-> (PollingStatus -> IO PollingStatus)
-> Maybe PollingStatus
-> IO PollingStatus
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
         ([Char] -> IO PollingStatus
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> IO PollingStatus) -> [Char] -> IO PollingStatus
forall a b. (a -> b) -> a -> b
$ [Char]
"unexpected polling status " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CInt -> [Char]
forall a. Show a => a -> [Char]
show CInt
code)
         PollingStatus -> IO PollingStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
         (CInt -> Maybe PollingStatus
forall a. FromCInt a => CInt -> Maybe a
fromCInt 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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CString -> IO ByteString
B.packCString CString
cstr
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
  IO ConnStatus
-> (ConnStatus -> IO ConnStatus)
-> Maybe ConnStatus
-> IO ConnStatus
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
    ([Char] -> IO ConnStatus
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> IO ConnStatus) -> [Char] -> IO ConnStatus
forall a b. (a -> b) -> a -> b
$ [Char]
"Unknown connection status " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CInt -> [Char]
forall a. Show a => a -> [Char]
show CInt
stat)
    ConnStatus -> IO ConnStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    (CInt -> Maybe ConnStatus
forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
stat)
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
  IO TransactionStatus
-> (TransactionStatus -> IO TransactionStatus)
-> Maybe TransactionStatus
-> IO TransactionStatus
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
    ([Char] -> IO TransactionStatus
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> IO TransactionStatus) -> [Char] -> IO TransactionStatus
forall a b. (a -> b) -> a -> b
$ [Char]
"Unknown transaction status " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CInt -> [Char]
forall a. Show a => a -> [Char]
show CInt
stat)
    TransactionStatus -> IO TransactionStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    (CInt -> Maybe TransactionStatus
forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
stat)
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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 a b. (a -> b) -> IO a -> IO b
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 a b. (a -> b) -> IO a -> IO b
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 = (CInt -> Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> IO a -> IO b
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
c_PQlibVersion
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Fd
forall a. Maybe a
Nothing
         CInt
_  -> Maybe Fd -> IO (Maybe Fd)
forall a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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
$c== :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
/= :: Result -> Result -> Bool
Eq, Int -> Result -> [Char] -> [Char]
[Result] -> [Char] -> [Char]
Result -> [Char]
(Int -> Result -> [Char] -> [Char])
-> (Result -> [Char])
-> ([Result] -> [Char] -> [Char])
-> Show Result
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Result -> [Char] -> [Char]
showsPrec :: Int -> Result -> [Char] -> [Char]
$cshow :: Result -> [Char]
show :: Result -> [Char]
$cshowList :: [Result] -> [Char] -> [Char]
showList :: [Result] -> [Char] -> [Char]
Show)
unsafeUseParamAsCString :: (B.ByteString, Format) -> (CString -> IO a) -> IO a
unsafeUseParamAsCString :: forall a. (ByteString, Format) -> (CString -> IO a) -> IO a
unsafeUseParamAsCString (ByteString
bs, Format
format) CString -> IO a
kont =
    case Format
format of
        Format
Binary -> ByteString -> (CStringLen -> IO a) -> IO a
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs CStringLen -> IO a
forall {a}. (Eq a, Num a) => (CString, a) -> IO a
kont'
        Format
Text   -> ByteString -> (CString -> IO a) -> IO a
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
bs CString -> IO a
kont
  where
    kont' :: (CString, a) -> IO a
kont' (CString
ptr, a
0) = if CString
ptr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr then CString -> IO a
kont CString
forall a. Ptr a
emptyPtr else CString -> IO a
kont CString
ptr
    kont' (CString
ptr, a
_) = CString -> IO a
kont CString
ptr
withParams :: [Maybe (Oid, B.ByteString, Format)]
           -> (CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a)
           -> IO a
withParams :: forall a.
[Maybe (Oid, ByteString, Format)]
-> (CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a)
-> IO a
withParams [Maybe (Oid, ByteString, Format)]
params CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a
action =
    Int -> [Oid] -> (Ptr Oid -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [Oid]
oids ((Ptr Oid -> IO a) -> IO a) -> (Ptr Oid -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Oid
ts ->
        (Maybe (ByteString, Format) -> (CString -> IO a) -> IO a)
-> [Maybe (ByteString, Format)] -> ([CString] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany (((ByteString, Format) -> (CString -> IO a) -> IO a)
-> Maybe (ByteString, Format) -> (CString -> IO a) -> IO a
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith (ByteString, Format) -> (CString -> IO a) -> IO a
forall a. (ByteString, Format) -> (CString -> IO a) -> IO a
unsafeUseParamAsCString) [Maybe (ByteString, Format)]
values (([CString] -> IO a) -> IO a) -> ([CString] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
            Int -> [CString] -> (Ptr CString -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CString]
c_values ((Ptr CString -> IO a) -> IO a) -> (Ptr CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
                Int -> [CInt] -> (Ptr CInt -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
c_lengths ((Ptr CInt -> IO a) -> IO a) -> (Ptr CInt -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
                    Int -> [CInt] -> (Ptr CInt -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
formats ((Ptr CInt -> IO a) -> IO a) -> (Ptr CInt -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
fs ->
                        CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a
action (Int -> CInt
intToCInt Int
n) Ptr Oid
ts Ptr CString
vs Ptr CInt
ls Ptr CInt
fs
  where
    AccumParams Int
n [Oid]
oids [Maybe (ByteString, Format)]
values [CInt]
c_lengths [CInt]
formats =
        (Maybe (Oid, ByteString, Format) -> AccumParams -> AccumParams)
-> AccumParams -> [Maybe (Oid, ByteString, Format)] -> AccumParams
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Maybe (Oid, ByteString, Format) -> AccumParams -> AccumParams
accum (Int
-> [Oid]
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumParams
AccumParams Int
0 [] [] [] []) [Maybe (Oid, ByteString, Format)]
params
    accum :: Maybe (Oid, B.ByteString, Format) -> AccumParams -> AccumParams
    accum :: Maybe (Oid, ByteString, Format) -> AccumParams -> AccumParams
accum Maybe (Oid, ByteString, Format)
Nothing ~(AccumParams Int
i [Oid]
a [Maybe (ByteString, Format)]
b [CInt]
c [CInt]
d) =
        Int
-> [Oid]
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumParams
AccumParams (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Oid
invalidOid Oid -> [Oid] -> [Oid]
forall a. a -> [a] -> [a]
: [Oid]
a) (Maybe (ByteString, Format)
forall a. Maybe a
Nothing Maybe (ByteString, Format)
-> [Maybe (ByteString, Format)] -> [Maybe (ByteString, Format)]
forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
b) (CInt
0 CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
c) (CInt
0 CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
d)
    accum (Just (Oid
t,ByteString
v,Format
f)) ~(AccumParams Int
i [Oid]
xs [Maybe (ByteString, Format)]
ys [CInt]
zs [CInt]
ws)  =
        let !z :: CInt
z = Int -> CInt
intToCInt (ByteString -> Int
B.length ByteString
v)
            !w :: CInt
w = Format -> CInt
forall a. ToCInt a => a -> CInt
toCInt Format
f
        in Int
-> [Oid]
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumParams
AccumParams (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Oid
t Oid -> [Oid] -> [Oid]
forall a. a -> [a] -> [a]
: [Oid]
xs) ((ByteString, Format) -> Maybe (ByteString, Format)
forall a. a -> Maybe a
Just (ByteString
v, Format
f) Maybe (ByteString, Format)
-> [Maybe (ByteString, Format)] -> [Maybe (ByteString, Format)]
forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
ys) (CInt
z CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
zs) (CInt
w CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
ws)
intToCInt :: Int -> CInt
intToCInt :: Int -> CInt
intToCInt = Int -> CInt
forall a. Enum a => Int -> a
toEnum
data AccumParams = AccumParams !Int ![Oid] ![Maybe (B.ByteString, Format)] ![CInt] ![CInt]
withParamsPrepared :: [Maybe (B.ByteString, Format)]
                   -> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a)
                   -> IO a
withParamsPrepared :: forall a.
[Maybe (ByteString, Format)]
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a) -> IO a
withParamsPrepared [Maybe (ByteString, Format)]
params CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a
action =
    (Maybe (ByteString, Format) -> (CString -> IO a) -> IO a)
-> [Maybe (ByteString, Format)] -> ([CString] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany (((ByteString, Format) -> (CString -> IO a) -> IO a)
-> Maybe (ByteString, Format) -> (CString -> IO a) -> IO a
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith (ByteString, Format) -> (CString -> IO a) -> IO a
forall a. (ByteString, Format) -> (CString -> IO a) -> IO a
unsafeUseParamAsCString) [Maybe (ByteString, Format)]
values (([CString] -> IO a) -> IO a) -> ([CString] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
        Int -> [CString] -> (Ptr CString -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CString]
c_values ((Ptr CString -> IO a) -> IO a) -> (Ptr CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
            Int -> [CInt] -> (Ptr CInt -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
c_lengths ((Ptr CInt -> IO a) -> IO a) -> (Ptr CInt -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
                Int -> [CInt] -> (Ptr CInt -> IO a) -> IO a
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
formats ((Ptr CInt -> IO a) -> IO a) -> (Ptr CInt -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
fs ->
                    CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a
action (Int -> CInt
intToCInt Int
n) Ptr CString
vs Ptr CInt
ls Ptr CInt
fs
  where
    AccumPrepParams Int
n [Maybe (ByteString, Format)]
values [CInt]
c_lengths [CInt]
formats =
        (Maybe (ByteString, Format) -> AccumPrepParams -> AccumPrepParams)
-> AccumPrepParams
-> [Maybe (ByteString, Format)]
-> AccumPrepParams
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Maybe (ByteString, Format) -> AccumPrepParams -> AccumPrepParams
accum (Int
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumPrepParams
AccumPrepParams Int
0 [] [] []) [Maybe (ByteString, Format)]
params
    accum :: Maybe (B.ByteString, Format) -> AccumPrepParams -> AccumPrepParams
    accum :: Maybe (ByteString, Format) -> AccumPrepParams -> AccumPrepParams
accum Maybe (ByteString, Format)
Nothing ~(AccumPrepParams Int
i [Maybe (ByteString, Format)]
a [CInt]
b [CInt]
c) =
        Int
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumPrepParams
AccumPrepParams (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Maybe (ByteString, Format)
forall a. Maybe a
Nothing Maybe (ByteString, Format)
-> [Maybe (ByteString, Format)] -> [Maybe (ByteString, Format)]
forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
a) (CInt
0 CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
b) (CInt
0 CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
c)
    accum (Just (ByteString
v, Format
f)) ~(AccumPrepParams Int
i [Maybe (ByteString, Format)]
xs [CInt]
ys [CInt]
zs) =
        let !y :: CInt
y = Int -> CInt
intToCInt (ByteString -> Int
B.length ByteString
v)
            !z :: CInt
z = Format -> CInt
forall a. ToCInt a => a -> CInt
toCInt Format
f
        in Int
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumPrepParams
AccumPrepParams (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) ((ByteString, Format) -> Maybe (ByteString, Format)
forall a. a -> Maybe a
Just (ByteString
v, Format
f) Maybe (ByteString, Format)
-> [Maybe (ByteString, Format)] -> [Maybe (ByteString, Format)]
forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
xs) (CInt
y CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
ys) (CInt
z CInt -> [CInt] -> [CInt]
forall a. a -> [a] -> [a]
: [CInt]
zs)
data AccumPrepParams = AccumPrepParams !Int ![Maybe (B.ByteString, Format)] ![CInt] ![CInt]
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 =
    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 ->
            [Maybe (Oid, ByteString, Format)]
-> (CInt
    -> Ptr Oid
    -> Ptr CString
    -> Ptr CInt
    -> Ptr CInt
    -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a.
[Maybe (Oid, ByteString, Format)]
-> (CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a)
-> IO a
withParams [Maybe (Oid, ByteString, Format)]
params ((CInt
  -> Ptr Oid
  -> Ptr CString
  -> Ptr CInt
  -> Ptr CInt
  -> IO (Ptr PGresult))
 -> IO (Ptr PGresult))
-> (CInt
    -> Ptr Oid
    -> Ptr CString
    -> Ptr CInt
    -> Ptr CInt
    -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CInt
n Ptr Oid
ts Ptr CString
vs Ptr CInt
ls 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
    !f :: CInt
f = Format -> CInt
forall a. ToCInt a => a -> CInt
toCInt Format
rFmt
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]
 -> (Int -> Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> Maybe [Oid]
-> (Int -> Ptr Oid -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b c.
(a -> (Int -> Ptr b -> IO c) -> IO c)
-> Maybe a -> (Int -> Ptr b -> IO c) -> IO c
maybeWithInt [Oid] -> (Int -> Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen Maybe [Oid]
mParamTypes ((Int -> Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult))
-> (Int -> Ptr Oid -> IO (Ptr PGresult)) -> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \Int
l Ptr Oid
o ->
                    Ptr PGconn
-> CString -> CString -> CInt -> Ptr Oid -> IO (Ptr PGresult)
c_PQprepare Ptr PGconn
c CString
s CString
q (Int -> CInt
intToCInt Int
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)]
params 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, Format)]
-> (CInt
    -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a.
[Maybe (ByteString, Format)]
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a) -> IO a
withParamsPrepared [Maybe (ByteString, Format)]
params ((CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO (Ptr PGresult))
 -> IO (Ptr PGresult))
-> (CInt
    -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO (Ptr PGresult))
-> IO (Ptr PGresult)
forall a b. (a -> b) -> a -> b
$ \CInt
n Ptr CString
vs Ptr CInt
ls 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
      !f :: CInt
f = Format -> CInt
forall a. ToCInt a => a -> CInt
toCInt Format
rFmt
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
resultStatus :: Result
             -> IO ExecStatus
resultStatus :: Result -> IO ExecStatus
resultStatus Result
result = Result -> (Ptr PGresult -> IO CInt) -> IO ExecStatus
forall b. FromCInt b => Result -> (Ptr PGresult -> IO CInt) -> 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
$ ExecStatus -> CInt
forall a. ToCInt a => a -> CInt
toCInt 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 a. a -> IO a
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
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
$ FieldCode -> CInt
forall a. ToCInt a => a -> CInt
toCInt 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 a. a -> IO a
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 a. a -> IO a
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 stock (Column -> Column -> Bool
(Column -> Column -> Bool)
-> (Column -> Column -> Bool) -> Eq Column
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Column -> Column -> Bool
== :: Column -> Column -> Bool
$c/= :: Column -> Column -> Bool
/= :: 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
$ccompare :: Column -> Column -> Ordering
compare :: Column -> Column -> Ordering
$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
>= :: Column -> Column -> Bool
$cmax :: Column -> Column -> Column
max :: Column -> Column -> Column
$cmin :: Column -> Column -> Column
min :: Column -> Column -> Column
Ord, Int -> Column -> [Char] -> [Char]
[Column] -> [Char] -> [Char]
Column -> [Char]
(Int -> Column -> [Char] -> [Char])
-> (Column -> [Char])
-> ([Column] -> [Char] -> [Char])
-> Show Column
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Column -> [Char] -> [Char]
showsPrec :: Int -> Column -> [Char] -> [Char]
$cshow :: Column -> [Char]
show :: Column -> [Char]
$cshowList :: [Column] -> [Char] -> [Char]
showList :: [Column] -> [Char] -> [Char]
Show)
  deriving newtype (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
$csucc :: Column -> Column
succ :: Column -> Column
$cpred :: Column -> Column
pred :: Column -> Column
$ctoEnum :: Int -> Column
toEnum :: Int -> Column
$cfromEnum :: Column -> Int
fromEnum :: Column -> Int
$cenumFrom :: Column -> [Column]
enumFrom :: Column -> [Column]
$cenumFromThen :: Column -> Column -> [Column]
enumFromThen :: Column -> Column -> [Column]
$cenumFromTo :: Column -> Column -> [Column]
enumFromTo :: Column -> Column -> [Column]
$cenumFromThenTo :: Column -> Column -> Column -> [Column]
enumFromThenTo :: Column -> Column -> 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
$c+ :: Column -> Column -> Column
+ :: Column -> Column -> Column
$c- :: Column -> Column -> Column
- :: Column -> Column -> Column
$c* :: Column -> Column -> Column
* :: Column -> Column -> Column
$cnegate :: Column -> Column
negate :: Column -> Column
$cabs :: Column -> Column
abs :: Column -> Column
$csignum :: Column -> Column
signum :: Column -> Column
$cfromInteger :: Integer -> Column
fromInteger :: Integer -> Column
Num)
newtype Row    = Row CInt
  deriving stock (Row -> Row -> Bool
(Row -> Row -> Bool) -> (Row -> Row -> Bool) -> Eq Row
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Row -> Row -> Bool
== :: Row -> Row -> Bool
$c/= :: Row -> Row -> Bool
/= :: 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
$ccompare :: Row -> Row -> Ordering
compare :: Row -> Row -> Ordering
$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
>= :: Row -> Row -> Bool
$cmax :: Row -> Row -> Row
max :: Row -> Row -> Row
$cmin :: Row -> Row -> Row
min :: Row -> Row -> Row
Ord, Int -> Row -> [Char] -> [Char]
[Row] -> [Char] -> [Char]
Row -> [Char]
(Int -> Row -> [Char] -> [Char])
-> (Row -> [Char]) -> ([Row] -> [Char] -> [Char]) -> Show Row
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Row -> [Char] -> [Char]
showsPrec :: Int -> Row -> [Char] -> [Char]
$cshow :: Row -> [Char]
show :: Row -> [Char]
$cshowList :: [Row] -> [Char] -> [Char]
showList :: [Row] -> [Char] -> [Char]
Show)
  deriving newtype (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
$csucc :: Row -> Row
succ :: Row -> Row
$cpred :: Row -> Row
pred :: Row -> Row
$ctoEnum :: Int -> Row
toEnum :: Int -> Row
$cfromEnum :: Row -> Int
fromEnum :: Row -> Int
$cenumFrom :: Row -> [Row]
enumFrom :: Row -> [Row]
$cenumFromThen :: Row -> Row -> [Row]
enumFromThen :: Row -> Row -> [Row]
$cenumFromTo :: Row -> Row -> [Row]
enumFromTo :: Row -> Row -> [Row]
$cenumFromThenTo :: Row -> Row -> Row -> [Row]
enumFromThenTo :: Row -> Row -> 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
$c+ :: Row -> Row -> Row
+ :: Row -> Row -> Row
$c- :: Row -> Row -> Row
- :: Row -> Row -> Row
$c* :: Row -> Row -> Row
* :: Row -> Row -> Row
$cnegate :: Row -> Row
negate :: Row -> Row
$cabs :: Row -> Row
abs :: Row -> Row
$csignum :: Row -> Row
signum :: Row -> Row
$cfromInteger :: Integer -> Row
fromInteger :: Integer -> Row
Num)
toColumn :: (Integral a) => a -> Column
toColumn :: forall a. Integral a => 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 :: forall a. Integral a => 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Column
forall a. Maybe a
Nothing
         else Maybe Column -> IO (Maybe Column)
forall a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 b. FromCInt b => Result -> (Ptr PGresult -> IO CInt) -> 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
      case CInt -> Maybe Bool
forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
isnull of
        Just Bool
True  -> Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
        Just Bool
False -> 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 a. a -> IO a
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
        Maybe Bool
Nothing -> [Char] -> IO (Maybe ByteString)
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> IO (Maybe ByteString))
-> [Char] -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ [Char]
"fromCInt @Bool " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CInt -> [Char]
forall a. Show a => a -> [Char]
show CInt
isnull
    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
      case CInt -> Maybe Bool
forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
isnull of
        Just Bool
True  -> Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
        Just Bool
False -> 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 a b. (a -> b) -> IO a -> IO b
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 a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CStringLen -> IO ByteString
B.packCStringLen (CString
cstr, Int
l)
        Maybe Bool
Nothing -> [Char] -> IO (Maybe ByteString)
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> IO (Maybe ByteString))
-> [Char] -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ [Char]
"fromCInt @Bool " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CInt -> [Char]
forall a. Show a => a -> [Char]
show CInt
isnull
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 b. FromCInt b => Result -> (Ptr PGresult -> IO CInt) -> 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 a b. (a -> b) -> IO a -> IO b
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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
$c== :: CopyInResult -> CopyInResult -> Bool
== :: CopyInResult -> CopyInResult -> Bool
$c/= :: CopyInResult -> CopyInResult -> Bool
/= :: CopyInResult -> CopyInResult -> Bool
Eq, Int -> CopyInResult -> [Char] -> [Char]
[CopyInResult] -> [Char] -> [Char]
CopyInResult -> [Char]
(Int -> CopyInResult -> [Char] -> [Char])
-> (CopyInResult -> [Char])
-> ([CopyInResult] -> [Char] -> [Char])
-> Show CopyInResult
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CopyInResult -> [Char] -> [Char]
showsPrec :: Int -> CopyInResult -> [Char] -> [Char]
$cshow :: CopyInResult -> [Char]
show :: CopyInResult -> [Char]
$cshowList :: [CopyInResult] -> [Char] -> [Char]
showList :: [CopyInResult] -> [Char] -> [Char]
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CopyInResult
CopyInWouldBlock
                 | Bool
otherwise = CopyInResult -> IO CopyInResult
forall a. a -> IO a
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 -> [Char] -> [Char]
[CopyOutResult] -> [Char] -> [Char]
CopyOutResult -> [Char]
(Int -> CopyOutResult -> [Char] -> [Char])
-> (CopyOutResult -> [Char])
-> ([CopyOutResult] -> [Char] -> [Char])
-> Show CopyOutResult
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CopyOutResult -> [Char] -> [Char]
showsPrec :: Int -> CopyOutResult -> [Char] -> [Char]
$cshow :: CopyOutResult -> [Char]
show :: CopyOutResult -> [Char]
$cshowList :: [CopyOutResult] -> [Char] -> [Char]
showList :: [CopyOutResult] -> [Char] -> [Char]
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
$! Bool -> CInt
forall a. ToCInt a => a -> CInt
toCInt 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutError
             Ordering
EQ -> CopyOutResult -> IO CopyOutResult
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutDone
             Ordering
GT -> CopyOutResult -> IO CopyOutResult
forall a. a -> IO a
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 a. a -> IO a
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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 =
    Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 ->
            [Maybe (Oid, ByteString, Format)]
-> (CInt
    -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO CInt)
-> IO CInt
forall a.
[Maybe (Oid, ByteString, Format)]
-> (CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a)
-> IO a
withParams [Maybe (Oid, ByteString, Format)]
params ((CInt
  -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO CInt)
 -> IO CInt)
-> (CInt
    -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO CInt)
-> IO CInt
forall a b. (a -> b) -> a -> b
$ \CInt
n Ptr Oid
ts Ptr CString
vs Ptr CInt
ls 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
      !f :: CInt
f = Format -> CInt
forall a. ToCInt a => a -> CInt
toCInt Format
rFmt
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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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] -> (Int -> Ptr Oid -> IO CInt) -> IO CInt)
-> Maybe [Oid] -> (Int -> Ptr Oid -> IO CInt) -> IO CInt
forall a b c.
(a -> (Int -> Ptr b -> IO c) -> IO c)
-> Maybe a -> (Int -> Ptr b -> IO c) -> IO c
maybeWithInt [Oid] -> (Int -> Ptr Oid -> IO CInt) -> IO CInt
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen Maybe [Oid]
mParamTypes ((Int -> Ptr Oid -> IO CInt) -> IO CInt)
-> (Int -> Ptr Oid -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Int
l Ptr Oid
o ->
                    Ptr PGconn -> CString -> CString -> CInt -> Ptr Oid -> IO CInt
c_PQsendPrepare Ptr PGconn
c CString
s CString
q (Int -> CInt
intToCInt Int
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)]
params Format
rFmt =
    Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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, Format)]
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO CInt)
-> IO CInt
forall a.
[Maybe (ByteString, Format)]
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a) -> IO a
withParamsPrepared [Maybe (ByteString, Format)]
params ((CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO CInt)
 -> IO CInt)
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO CInt)
-> IO CInt
forall a b. (a -> b) -> a -> b
$ \CInt
n Ptr CString
vs Ptr CInt
ls 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
      !f :: CInt
f = Format -> CInt
forall a. ToCInt a => a -> CInt
toCInt Format
rFmt
sendDescribePrepared :: Connection
                     -> B.ByteString 
                     -> IO Bool
sendDescribePrepared :: Connection -> ByteString -> IO Bool
sendDescribePrepared Connection
connection ByteString
stmtName =
    Connection -> (Ptr PGconn -> IO CInt) -> IO Bool
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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
       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 (Bool -> CInt
forall a. ToCInt a => a -> CInt
toCInt Bool
blocking)
       Bool -> IO Bool
forall a. a -> IO a
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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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 b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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
$c== :: FlushStatus -> FlushStatus -> Bool
== :: FlushStatus -> FlushStatus -> Bool
$c/= :: FlushStatus -> FlushStatus -> Bool
/= :: FlushStatus -> FlushStatus -> Bool
Eq, Int -> FlushStatus -> [Char] -> [Char]
[FlushStatus] -> [Char] -> [Char]
FlushStatus -> [Char]
(Int -> FlushStatus -> [Char] -> [Char])
-> (FlushStatus -> [Char])
-> ([FlushStatus] -> [Char] -> [Char])
-> Show FlushStatus
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> FlushStatus -> [Char] -> [Char]
showsPrec :: Int -> FlushStatus -> [Char] -> [Char]
$cshow :: FlushStatus -> [Char]
show :: FlushStatus -> [Char]
$cshowList :: [FlushStatus] -> [Char] -> [Char]
showList :: [FlushStatus] -> [Char] -> [Char]
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushOk
         CInt
1 -> FlushStatus -> IO FlushStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushWriting
         CInt
_ -> FlushStatus -> IO FlushStatus
forall a. a -> IO a
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
$c== :: Cancel -> Cancel -> Bool
== :: Cancel -> Cancel -> Bool
$c/= :: Cancel -> Cancel -> Bool
/= :: Cancel -> Cancel -> Bool
Eq, Int -> Cancel -> [Char] -> [Char]
[Cancel] -> [Char] -> [Char]
Cancel -> [Char]
(Int -> Cancel -> [Char] -> [Char])
-> (Cancel -> [Char])
-> ([Cancel] -> [Char] -> [Char])
-> Show Cancel
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Cancel -> [Char] -> [Char]
showsPrec :: Int -> Cancel -> [Char] -> [Char]
$cshow :: Cancel -> [Char]
show :: Cancel -> [Char]
$cshowList :: [Cancel] -> [Char] -> [Char]
showList :: [Cancel] -> [Char] -> [Char]
Show)
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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
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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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
setErrorVerbosity :: Connection
                  -> Verbosity
                  -> IO Verbosity
setErrorVerbosity :: Connection -> Verbosity -> IO Verbosity
setErrorVerbosity Connection
connection Verbosity
verbosity =
    Connection -> (Ptr PGconn -> IO CInt) -> IO Verbosity
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> 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
$ Verbosity -> CInt
forall a. ToCInt a => a -> CInt
toCInt Verbosity
verbosity
enumFromConn :: FromCInt b
             => Connection
             -> (Ptr PGconn -> IO CInt)
             -> IO b
enumFromConn :: forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection Ptr PGconn -> IO CInt
f = Connection -> (Ptr PGconn -> IO CInt) -> IO CInt
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
f IO CInt -> (CInt -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO b -> (b -> IO b) -> Maybe b -> IO b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> IO b
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"enumFromConn") b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe b -> IO b) -> (CInt -> Maybe b) -> CInt -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Maybe b
forall a. FromCInt a => CInt -> Maybe a
fromCInt
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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 :: forall b. 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 :: forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result Ptr PGresult -> IO a
f = (a -> b) -> IO a -> IO b
forall a b. (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 :: FromCInt b
               => Result
               -> (Ptr PGresult -> IO CInt)
               -> IO b
enumFromResult :: forall b. FromCInt b => Result -> (Ptr PGresult -> IO CInt) -> IO b
enumFromResult Result
result Ptr PGresult -> IO CInt
f = Result -> (Ptr PGresult -> IO CInt) -> IO CInt
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result Ptr PGresult -> IO CInt
f IO CInt -> (CInt -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO b -> (b -> IO b) -> Maybe b -> IO b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> IO b
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"enumFromResult") b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe b -> IO b) -> (CInt -> Maybe b) -> CInt -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Maybe b
forall a. FromCInt a => CInt -> Maybe a
fromCInt
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 :: forall a.
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 a. a -> IO a
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 a b. (a -> b) -> IO a -> IO b
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 a. a -> IO a
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
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 a. a -> IO a
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 a. a -> IO a
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)
          CSize
len  <- Ptr PGnotice -> IO CSize
pgNoticePeekLen Ptr PGnotice
np
          Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
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
pgNoticeOffsetStr (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
len)
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
$c== :: LoFd -> LoFd -> Bool
== :: LoFd -> LoFd -> Bool
$c/= :: LoFd -> LoFd -> Bool
/= :: 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
$ccompare :: LoFd -> LoFd -> Ordering
compare :: LoFd -> LoFd -> Ordering
$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
>= :: LoFd -> LoFd -> Bool
$cmax :: LoFd -> LoFd -> LoFd
max :: LoFd -> LoFd -> LoFd
$cmin :: LoFd -> LoFd -> LoFd
min :: LoFd -> LoFd -> LoFd
Ord, Int -> LoFd -> [Char] -> [Char]
[LoFd] -> [Char] -> [Char]
LoFd -> [Char]
(Int -> LoFd -> [Char] -> [Char])
-> (LoFd -> [Char]) -> ([LoFd] -> [Char] -> [Char]) -> Show LoFd
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> LoFd -> [Char] -> [Char]
showsPrec :: Int -> LoFd -> [Char] -> [Char]
$cshow :: LoFd -> [Char]
show :: LoFd -> [Char]
$cshowList :: [LoFd] -> [Char] -> [Char]
showList :: [LoFd] -> [Char] -> [Char]
Show)
loMode :: IOMode -> CInt
loMode :: IOMode -> CInt
loMode = IOMode -> CInt
forall a. ToCInt a => a -> CInt
toCInt
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Oid
forall a. Maybe a
Nothing
               | Bool
otherwise         = Maybe Oid -> IO (Maybe Oid)
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing else Maybe Int -> IO (Maybe Int)
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ()
forall a. Maybe a
Nothing else Maybe () -> IO (Maybe ())
forall a. a -> IO a
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 -> [Char] -> IO (Maybe Oid)
loImport Connection
connection [Char]
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
        [Char] -> (CString -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
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 -> [Char] -> Oid -> IO (Maybe Oid)
loImportWithOid Connection
connection [Char]
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
        [Char] -> (CString -> IO (Maybe Oid)) -> IO (Maybe Oid)
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
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 -> [Char] -> IO (Maybe ())
loExport Connection
connection Oid
oid [Char]
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
        [Char] -> (CString -> IO (Maybe ())) -> IO (Maybe ())
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
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 a. a -> IO a
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 a. a -> IO a
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 (SeekMode -> CInt
forall a. ToCInt a => a -> CInt
toCInt SeekMode
SeekFromEnd)
                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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LoFd
forall a. Maybe a
Nothing
                  CInt
_  -> Maybe LoFd -> IO (Maybe LoFd)
forall a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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
$ SeekMode -> CInt
forall a. ToCInt a => a -> CInt
toCInt SeekMode
seekmode
        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