{-# 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
connectdb :: B.ByteString
-> IO Connection
connectdb :: ByteString -> IO Connection
connectdb ByteString
conninfo =
forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
Ptr PGconn
connPtr <- forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
conninfo CString -> IO (Ptr PGconn)
c_PQconnectdb
if Ptr PGconn
connPtr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"libpq failed to allocate a PGconn structure"
else do
MVar (Ptr CNoticeBuffer)
noticeBuffer <- forall a. a -> IO (MVar a)
newMVar forall a. Ptr a
nullPtr
ForeignPtr PGconn
connection <- 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)
forall (m :: * -> *) a. Monad m => a -> m a
return 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 =
forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
Ptr PGconn
connPtr <- forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
connStr CString -> IO (Ptr PGconn)
c_PQconnectStart
if Ptr PGconn
connPtr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"libpq failed to allocate a PGconn structure"
else do
MVar (Ptr CNoticeBuffer)
noticeBuffer <- forall a. a -> IO (MVar a)
newMVar forall a. Ptr a
nullPtr
ForeignPtr PGconn
connection <- 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)
forall (m :: * -> *) a. Monad m => a -> m a
return 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 <- forall a. MVar a -> a -> IO a
swapMVar MVar (Ptr CNoticeBuffer)
noticeBuffer 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 <- forall a. a -> IO (MVar a)
newMVar IO ()
fin
forall a. Ptr a -> IO () -> IO (ForeignPtr a)
FC.newForeignPtr Ptr a
ptr forall a b. (a -> b) -> a -> b
$ forall a. MVar a -> IO (Maybe a)
tryTakeMVar MVar (IO ())
mv forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return ()) forall a. a -> a
id
newNullConnection :: IO Connection
newNullConnection :: IO Connection
newNullConnection = do
ForeignPtr PGconn
connection <- forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ forall a. Ptr a
nullPtr
MVar (Ptr CNoticeBuffer)
noticeBuffer <- forall a. a -> IO (MVar a)
newMVar forall a. Ptr a
nullPtr
forall (m :: * -> *) a. Monad m => a -> m a
return 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)
_) = forall a. ForeignPtr a -> Ptr a
Unsafe.unsafeForeignPtrToPtr ForeignPtr PGconn
x forall a. Eq a => a -> a -> Bool
== 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 = 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 =
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 <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
poller
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"unexpected polling status " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show CInt
code)
forall (m :: * -> *) a. Monad m => a -> m a
return
(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 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 =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr ->
do CString
cstr <- Ptr PGconn -> IO CString
f Ptr PGconn
ptr
if CString
cstr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just 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 <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQstatus
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"Unknown connection status " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show CInt
stat)
forall (m :: * -> *) a. Monad m => a -> m a
return
(forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
stat)
transactionStatus :: Connection
-> IO TransactionStatus
transactionStatus :: Connection -> IO TransactionStatus
transactionStatus Connection
connection = do
CInt
stat <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQtransactionStatus
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"Unknown transaction status " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show CInt
stat)
forall (m :: * -> *) a. Monad m => a -> m a
return
(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 =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
connPtr ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
paramName 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 forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just 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 =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ 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 =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ 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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap 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 <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQsocket
case CInt
cFd of
-1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
CInt
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ CInt -> Fd
Fd CInt
cFd
backendPID :: Connection
-> IO CPid
backendPID :: Connection -> IO CPid
backendPID Connection
connection =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ 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 =
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 =
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
Eq, Int -> Result -> ShowS
[Result] -> ShowS
Result -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Result] -> ShowS
$cshowList :: [Result] -> ShowS
show :: Result -> [Char]
$cshow :: Result -> [Char]
showsPrec :: Int -> Result -> ShowS
$cshowsPrec :: Int -> Result -> ShowS
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) =
case Format
format of
Format
Binary -> forall a. ByteString -> (CString -> IO a) -> IO a
B.unsafeUseAsCString ByteString
bs
Format
Text -> forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
bs
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 =
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [Oid]
oids forall a b. (a -> b) -> a -> b
$ \Ptr Oid
ts ->
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany (forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith forall a. (ByteString, Format) -> (CString -> IO a) -> IO a
unsafeUseParamAsCString) [Maybe (ByteString, Format)]
values forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CString]
c_values forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
c_lengths forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
formats 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 =
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 forall a. Num a => a -> a -> a
+ Int
1) (Oid
invalidOid forall a. a -> [a] -> [a]
: [Oid]
a) (forall a. Maybe a
Nothing forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
b) (CInt
0 forall a. a -> [a] -> [a]
: [CInt]
c) (CInt
0 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 = forall a. ToCInt a => a -> CInt
toCInt Format
f
in Int
-> [Oid]
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumParams
AccumParams (Int
i forall a. Num a => a -> a -> a
+ Int
1) (Oid
t forall a. a -> [a] -> [a]
: [Oid]
xs) (forall a. a -> Maybe a
Just (ByteString
v, Format
f) forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
ys) (CInt
z forall a. a -> [a] -> [a]
: [CInt]
zs) (CInt
w forall a. a -> [a] -> [a]
: [CInt]
ws)
intToCInt :: Int -> CInt
intToCInt :: Int -> CInt
intToCInt = 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 =
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany (forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith forall a. (ByteString, Format) -> (CString -> IO a) -> IO a
unsafeUseParamAsCString) [Maybe (ByteString, Format)]
values forall a b. (a -> b) -> a -> b
$ \[CString]
c_values ->
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CString]
c_values forall a b. (a -> b) -> a -> b
$ \Ptr CString
vs ->
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
c_lengths forall a b. (a -> b) -> a -> b
$ \Ptr CInt
ls ->
forall a b. Storable a => Int -> [a] -> (Ptr a -> IO b) -> IO b
unsafeWithArray Int
n [CInt]
formats 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 =
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 forall a. Num a => a -> a -> a
+ Int
1) (forall a. Maybe a
Nothing forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
a) (CInt
0 forall a. a -> [a] -> [a]
: [CInt]
b) (CInt
0 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 = forall a. ToCInt a => a -> CInt
toCInt Format
f
in Int
-> [Maybe (ByteString, Format)]
-> [CInt]
-> [CInt]
-> AccumPrepParams
AccumPrepParams (Int
i forall a. Num a => a -> a -> a
+ Int
1) (forall a. a -> Maybe a
Just (ByteString
v, Format
f) forall a. a -> [a] -> [a]
: [Maybe (ByteString, Format)]
xs) (CInt
y forall a. a -> [a] -> [a]
: [CInt]
ys) (CInt
z 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 forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
p ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query 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 forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
statement forall a b. (a -> b) -> a -> b
$ \CString
s ->
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 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 = 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 forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName forall a b. (a -> b) -> a -> b
$ \CString
s ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query forall a b. (a -> b) -> a -> b
$ \CString
q ->
forall a b c.
(a -> (Int -> Ptr b -> IO c) -> IO c)
-> Maybe a -> (Int -> Ptr b -> IO c) -> IO c
maybeWithInt forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen Maybe [Oid]
mParamTypes 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 forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName forall a b. (a -> b) -> a -> b
$ \CString
s ->
forall a.
[Maybe (ByteString, Format)]
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a) -> IO a
withParamsPrepared [Maybe (ByteString, Format)]
params 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 = 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 forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName 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 forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
portalName 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 = 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 forall a b. (a -> b) -> a -> b
$ forall a. ToCInt a => a -> CInt
toCInt ExecStatus
es
CSize
len <- CString -> IO CSize
B.c_strlen CString
cstr
ForeignPtr Word8
fp <- forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ forall a b. (a -> b) -> a -> b
$ forall a b. Ptr a -> Ptr b
castPtr CString
cstr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
len
resultErrorMessage :: Result
-> IO (Maybe B.ByteString)
resultErrorMessage :: Result -> IO (Maybe ByteString)
resultErrorMessage = 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) = 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 =
forall a.
ForeignPtr a -> (Ptr a -> IO CString) -> IO (Maybe ByteString)
maybeBsFromForeignPtr ForeignPtr PGresult
fp forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
res ->
Ptr PGresult -> CInt -> IO CString
c_PQresultErrorField Ptr PGresult
res forall a b. (a -> b) -> a -> b
$ forall a. ToCInt a => a -> CInt
toCInt FieldCode
fieldcode
ntuples :: Result
-> IO Row
ntuples :: Result -> IO Row
ntuples Result
res = forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Row
toRow 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 = forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Column
toColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr PGresult -> CInt
c_PQnfields)
newtype Column = Col CInt
deriving stock (Column -> Column -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Column -> Column -> Bool
$c/= :: Column -> Column -> Bool
== :: Column -> Column -> Bool
$c== :: Column -> Column -> Bool
Eq, Eq Column
Column -> Column -> Bool
Column -> Column -> Ordering
Column -> Column -> Column
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Column -> Column -> Column
$cmin :: Column -> Column -> Column
max :: Column -> Column -> Column
$cmax :: Column -> Column -> Column
>= :: Column -> Column -> Bool
$c>= :: Column -> Column -> Bool
> :: Column -> Column -> Bool
$c> :: Column -> Column -> Bool
<= :: Column -> Column -> Bool
$c<= :: Column -> Column -> Bool
< :: Column -> Column -> Bool
$c< :: Column -> Column -> Bool
compare :: Column -> Column -> Ordering
$ccompare :: Column -> Column -> Ordering
Ord, Int -> Column -> ShowS
[Column] -> ShowS
Column -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Column] -> ShowS
$cshowList :: [Column] -> ShowS
show :: Column -> [Char]
$cshow :: Column -> [Char]
showsPrec :: Int -> Column -> ShowS
$cshowsPrec :: Int -> Column -> ShowS
Show)
deriving newtype (Int -> Column
Column -> Int
Column -> [Column]
Column -> Column
Column -> Column -> [Column]
Column -> Column -> Column -> [Column]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Column -> Column -> Column -> [Column]
$cenumFromThenTo :: Column -> Column -> Column -> [Column]
enumFromTo :: Column -> Column -> [Column]
$cenumFromTo :: Column -> Column -> [Column]
enumFromThen :: Column -> Column -> [Column]
$cenumFromThen :: Column -> Column -> [Column]
enumFrom :: Column -> [Column]
$cenumFrom :: Column -> [Column]
fromEnum :: Column -> Int
$cfromEnum :: Column -> Int
toEnum :: Int -> Column
$ctoEnum :: Int -> Column
pred :: Column -> Column
$cpred :: Column -> Column
succ :: Column -> Column
$csucc :: Column -> Column
Enum, Integer -> Column
Column -> Column
Column -> Column -> Column
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Column
$cfromInteger :: Integer -> Column
signum :: Column -> Column
$csignum :: Column -> Column
abs :: Column -> Column
$cabs :: Column -> Column
negate :: Column -> Column
$cnegate :: Column -> Column
* :: Column -> Column -> Column
$c* :: Column -> Column -> Column
- :: Column -> Column -> Column
$c- :: Column -> Column -> Column
+ :: Column -> Column -> Column
$c+ :: Column -> Column -> Column
Num)
newtype Row = Row CInt
deriving stock (Row -> Row -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Row -> Row -> Bool
$c/= :: Row -> Row -> Bool
== :: Row -> Row -> Bool
$c== :: Row -> Row -> Bool
Eq, Eq Row
Row -> Row -> Bool
Row -> Row -> Ordering
Row -> Row -> Row
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Row -> Row -> Row
$cmin :: Row -> Row -> Row
max :: Row -> Row -> Row
$cmax :: Row -> Row -> Row
>= :: Row -> Row -> Bool
$c>= :: Row -> Row -> Bool
> :: Row -> Row -> Bool
$c> :: Row -> Row -> Bool
<= :: Row -> Row -> Bool
$c<= :: Row -> Row -> Bool
< :: Row -> Row -> Bool
$c< :: Row -> Row -> Bool
compare :: Row -> Row -> Ordering
$ccompare :: Row -> Row -> Ordering
Ord, Int -> Row -> ShowS
[Row] -> ShowS
Row -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Row] -> ShowS
$cshowList :: [Row] -> ShowS
show :: Row -> [Char]
$cshow :: Row -> [Char]
showsPrec :: Int -> Row -> ShowS
$cshowsPrec :: Int -> Row -> ShowS
Show)
deriving newtype (Int -> Row
Row -> Int
Row -> [Row]
Row -> Row
Row -> Row -> [Row]
Row -> Row -> Row -> [Row]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Row -> Row -> Row -> [Row]
$cenumFromThenTo :: Row -> Row -> Row -> [Row]
enumFromTo :: Row -> Row -> [Row]
$cenumFromTo :: Row -> Row -> [Row]
enumFromThen :: Row -> Row -> [Row]
$cenumFromThen :: Row -> Row -> [Row]
enumFrom :: Row -> [Row]
$cenumFrom :: Row -> [Row]
fromEnum :: Row -> Int
$cfromEnum :: Row -> Int
toEnum :: Int -> Row
$ctoEnum :: Int -> Row
pred :: Row -> Row
$cpred :: Row -> Row
succ :: Row -> Row
$csucc :: Row -> Row
Enum, Integer -> Row
Row -> Row
Row -> Row -> Row
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Row
$cfromInteger :: Integer -> Row
signum :: Row -> Row
$csignum :: Row -> Row
abs :: Row -> Row
$cabs :: Row -> Row
negate :: Row -> Row
$cnegate :: Row -> Row
* :: Row -> Row -> Row
$c* :: Row -> Row -> Row
- :: Row -> Row -> Row
$c- :: Row -> Row -> Row
+ :: Row -> Row -> Row
$c+ :: Row -> Row -> Row
Num)
toColumn :: (Integral a) => a -> Column
toColumn :: forall a. Integral a => a -> Column
toColumn = CInt -> Column
Col forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 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 <- forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
resPtr ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
columnName forall a b. (a -> b) -> a -> b
$ \CString
columnNamePtr ->
Ptr PGresult -> CString -> IO CInt
c_PQfnumber Ptr PGresult
resPtr CString
columnNamePtr
if CInt
num forall a. Eq a => a -> a -> Bool
== -CInt
1
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ 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) = forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result 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) =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Column
Col forall a b. (a -> b) -> a -> b
$ forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result 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) =
forall b. FromCInt b => Result -> (Ptr PGresult -> IO CInt) -> IO b
enumFromResult Result
result 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) = forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result 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) = forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result 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) = forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result 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) =
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr PGresult
fp 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 forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
isnull of
Just Bool
True -> forall (m :: * -> *) a. Monad m => a -> m a
return 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' <- forall a. Ptr a -> IO () -> IO (ForeignPtr a)
FC.newForeignPtr (forall a b. Ptr a -> Ptr b
castPtr CString
cstr) IO ()
finalizer
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp' Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
l
Maybe Bool
Nothing -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"fromCInt @Bool " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show CInt
isnull
where
finalizer :: IO ()
finalizer = 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) =
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
res 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 forall a. FromCInt a => CInt -> Maybe a
fromCInt CInt
isnull of
Just Bool
True -> forall (m :: * -> *) a. Monad m => a -> m a
return 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 <- forall a b. (Integral a, Num b) => a -> b
fromIntegral 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
forall a. a -> Maybe a
Just 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 -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"fromCInt @Bool " forall a. [a] -> [a] -> [a]
++ 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) =
forall b. FromCInt b => Result -> (Ptr PGresult -> IO CInt) -> IO b
enumFromResult Result
result 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) =
forall a b.
(Integral a, Num b) =>
Result -> (Ptr PGresult -> IO a) -> IO b
numFromResult Result
result 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 = 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 =
forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result forall a b. (a -> b) -> a -> b
$ \Ptr PGresult
p -> Ptr PGresult -> CInt -> IO Oid
c_PQparamtype Ptr PGresult
p forall a b. (a -> b) -> a -> b
$ 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 = 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 = 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 =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(CString
from, Int
bslen) ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
err -> do
ByteString
xs <- Int -> (Ptr Word8 -> IO Int) -> IO ByteString
B.createAndTrim (Int
bslenforall a. Num a => a -> a -> a
*Int
2forall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ \Ptr Word8
to ->
forall a b. (Integral a, Num b) => a -> b
fromIntegral 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 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bslen) Ptr CInt
err
CInt
stat <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
err
case CInt
stat of
CInt
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ByteString
xs
CInt
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
escapeByteaConn :: Connection
-> B.ByteString
-> IO (Maybe B.ByteString)
escapeByteaConn :: Connection -> ByteString -> IO (Maybe ByteString)
escapeByteaConn Connection
connection ByteString
bs =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(CString
from, Int
bslen) ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca 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 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bslen) Ptr CSize
to_length
if Ptr Word8
to forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do ForeignPtr Word8
tofp <- forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr forall a. FunPtr (Ptr a -> IO ())
p_PQfreemem Ptr Word8
to
CSize
l <- forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
to_length
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
tofp Int
0 ((forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
l) forall a. Num a => a -> a -> a
- Int
1)
unescapeBytea :: B.ByteString
-> IO (Maybe B.ByteString)
unescapeBytea :: ByteString -> IO (Maybe ByteString)
unescapeBytea ByteString
bs =
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
bs forall a b. (a -> b) -> a -> b
$ \CString
from ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca 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 forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do ForeignPtr Word8
tofp <- forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr forall a. FunPtr (Ptr a -> IO ())
p_PQfreemem Ptr Word8
to
CSize
l <- forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
to_length
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
tofp Int
0 forall a b. (a -> b) -> a -> b
$ 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 =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
conn ->
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(CString
from, Int
bslen) -> forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
CString
bs'ptr <- Ptr PGconn -> CString -> CSize -> IO CString
c_PQescapeIdentifier Ptr PGconn
conn CString
from (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bslen)
if CString
bs'ptr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do
ByteString
bs' <- CString -> IO ByteString
B.packCString CString
bs'ptr
forall a. Ptr a -> IO ()
c_PQfreemem CString
bs'ptr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ByteString
bs'
data CopyInResult
= CopyInOk
| CopyInError
| CopyInWouldBlock
deriving (CopyInResult -> CopyInResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyInResult -> CopyInResult -> Bool
$c/= :: CopyInResult -> CopyInResult -> Bool
== :: CopyInResult -> CopyInResult -> Bool
$c== :: CopyInResult -> CopyInResult -> Bool
Eq, Int -> CopyInResult -> ShowS
[CopyInResult] -> ShowS
CopyInResult -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CopyInResult] -> ShowS
$cshowList :: [CopyInResult] -> ShowS
show :: CopyInResult -> [Char]
$cshow :: CopyInResult -> [Char]
showsPrec :: Int -> CopyInResult -> ShowS
$cshowsPrec :: Int -> CopyInResult -> ShowS
Show)
toCopyInResult :: CInt -> IO CopyInResult
toCopyInResult :: CInt -> IO CopyInResult
toCopyInResult CInt
n | CInt
n forall a. Ord a => a -> a -> Bool
< CInt
0 = forall (m :: * -> *) a. Monad m => a -> m a
return CopyInResult
CopyInError
| CInt
n forall a. Eq a => a -> a -> Bool
== CInt
0 = forall (m :: * -> *) a. Monad m => a -> m a
return CopyInResult
CopyInWouldBlock
| Bool
otherwise = 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 =
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bs 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 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
(forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CString -> CInt -> IO CInt
c_PQputCopyData Ptr PGconn
ptr CString
str (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 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
(forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CString -> IO CInt
c_PQputCopyEnd Ptr PGconn
ptr forall a. Ptr a
nullPtr)
putCopyEnd Connection
conn (Just ByteString
errormsg) =
CInt -> IO CopyInResult
toCopyInResult forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
(forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
errormsg forall a b. (a -> b) -> a -> b
$ \CString
errormsg_cstr ->
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CString -> IO CInt
c_PQputCopyEnd Ptr PGconn
ptr CString
errormsg_cstr)
data CopyOutResult
= CopyOutRow !B.ByteString
| CopyOutWouldBlock
| CopyOutDone
| CopyOutError
deriving Int -> CopyOutResult -> ShowS
[CopyOutResult] -> ShowS
CopyOutResult -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CopyOutResult] -> ShowS
$cshowList :: [CopyOutResult] -> ShowS
show :: CopyOutResult -> [Char]
$cshow :: CopyOutResult -> [Char]
showsPrec :: Int -> CopyOutResult -> ShowS
$cshowsPrec :: Int -> CopyOutResult -> ShowS
Show
getCopyData :: Connection -> Bool -> IO CopyOutResult
getCopyData :: Connection -> Bool -> IO CopyOutResult
getCopyData Connection
conn Bool
async = forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr Word8)
strp -> forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn 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 forall a b. (a -> b) -> a -> b
$! forall a. ToCInt a => a -> CInt
toCInt Bool
async
if CInt
len forall a. Ord a => a -> a -> Bool
<= CInt
0
then case forall a. Ord a => a -> a -> Ordering
compare CInt
len (-CInt
1) of
Ordering
LT -> forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutError
Ordering
EQ -> forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutDone
Ordering
GT -> forall (m :: * -> *) a. Monad m => a -> m a
return CopyOutResult
CopyOutWouldBlock
else do
ForeignPtr Word8
fp <- forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr forall a. FunPtr (Ptr a -> IO ())
p_PQfreemem forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Word8)
strp
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! ByteString -> CopyOutResult
CopyOutRow (ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp Int
0 (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 =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
p ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query 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 =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
statement forall a b. (a -> b) -> a -> b
$ \CString
s ->
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 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 = 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 =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName forall a b. (a -> b) -> a -> b
$ \CString
s ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
query forall a b. (a -> b) -> a -> b
$ \CString
q ->
forall a b c.
(a -> (Int -> Ptr b -> IO c) -> IO c)
-> Maybe a -> (Int -> Ptr b -> IO c) -> IO c
maybeWithInt forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen Maybe [Oid]
mParamTypes 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 =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName forall a b. (a -> b) -> a -> b
$ \CString
s ->
forall a.
[Maybe (ByteString, Format)]
-> (CInt -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a) -> IO a
withParamsPrepared [Maybe (ByteString, Format)]
params 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 = 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 =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
stmtName 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 =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
portalName 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 <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO (Ptr PGresult)
c_PQgetResult
if Ptr PGresult
resPtr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr PGresult -> Result
Result) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr PGresult -> IO ())
p_PQclear Ptr PGresult
resPtr
consumeInput :: Connection
-> IO Bool
consumeInput :: Connection -> IO Bool
consumeInput Connection
connection = 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 = 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 <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
ptr -> Ptr PGconn -> CInt -> IO CInt
c_PQsetnonblocking Ptr PGconn
ptr (forall a. ToCInt a => a -> CInt
toCInt Bool
blocking)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! CInt
stat forall a. Eq a => a -> a -> Bool
== CInt
0
isnonblocking :: Connection
-> IO Bool
isnonblocking :: Connection -> IO Bool
isnonblocking Connection
connection = 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 = 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlushStatus -> FlushStatus -> Bool
$c/= :: FlushStatus -> FlushStatus -> Bool
== :: FlushStatus -> FlushStatus -> Bool
$c== :: FlushStatus -> FlushStatus -> Bool
Eq, Int -> FlushStatus -> ShowS
[FlushStatus] -> ShowS
FlushStatus -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FlushStatus] -> ShowS
$cshowList :: [FlushStatus] -> ShowS
show :: FlushStatus -> [Char]
$cshow :: FlushStatus -> [Char]
showsPrec :: Int -> FlushStatus -> ShowS
$cshowsPrec :: Int -> FlushStatus -> ShowS
Show)
flush :: Connection
-> IO FlushStatus
flush :: Connection -> IO FlushStatus
flush Connection
connection =
do CInt
stat <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
c_PQflush
case CInt
stat of
CInt
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushOk
CInt
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushWriting
CInt
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return FlushStatus
FlushFailed
newtype Cancel = Cancel (ForeignPtr PGcancel) deriving (Cancel -> Cancel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cancel -> Cancel -> Bool
$c/= :: Cancel -> Cancel -> Bool
== :: Cancel -> Cancel -> Bool
$c== :: Cancel -> Cancel -> Bool
Eq, Int -> Cancel -> ShowS
[Cancel] -> ShowS
Cancel -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Cancel] -> ShowS
$cshowList :: [Cancel] -> ShowS
show :: Cancel -> [Char]
$cshow :: Cancel -> [Char]
showsPrec :: Int -> Cancel -> ShowS
$cshowsPrec :: Int -> Cancel -> ShowS
Show)
getCancel :: Connection
-> IO (Maybe Cancel)
getCancel :: Connection -> IO (Maybe Cancel)
getCancel Connection
connection =
forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection 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 forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do ForeignPtr PGcancel
fp <- forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr PGcancel -> IO ())
p_PQfreeCancel Ptr PGcancel
ptr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just 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) =
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr PGcancel
fp forall a b. (a -> b) -> a -> b
$ \Ptr PGcancel
ptr -> do
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
errbufsize 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 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
errbufsize
case CInt
res of
CInt
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right ()
CInt
_ -> forall a b. a -> Either a b
Left 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 =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection 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 forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do
Maybe Notify
result <- forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall a. Storable a => Ptr a -> IO a
peek Ptr Notify
mn
forall a. Ptr a -> IO ()
c_PQfreemem Ptr Notify
mn
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Notify
result
clientEncoding :: Connection
-> IO B.ByteString
clientEncoding :: Connection -> IO ByteString
clientEncoding Connection
connection =
forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection 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 <- forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ forall a b. (a -> b) -> a -> b
$ forall a b. Ptr a -> Ptr b
castPtr CString
cstr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fp Int
0 forall a b. (a -> b) -> a -> b
$ 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 <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c ->
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString ByteString
enc forall a b. (a -> b) -> a -> b
$ \CString
s ->
Ptr PGconn -> CString -> IO CInt
c_PQsetClientEncoding Ptr PGconn
c CString
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! CInt
stat forall a. Eq a => a -> a -> Bool
== CInt
0
setErrorVerbosity :: Connection
-> Verbosity
-> IO Verbosity
setErrorVerbosity :: Connection -> Verbosity -> IO Verbosity
setErrorVerbosity Connection
connection Verbosity
verbosity =
forall b.
FromCInt b =>
Connection -> (Ptr PGconn -> IO CInt) -> IO b
enumFromConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
p ->
Ptr PGconn -> CInt -> IO CInt
c_PQsetErrorVerbosity Ptr PGconn
p forall a b. (a -> b) -> a -> b
$ 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 = forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO CInt
f forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"enumFromConn") forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 =
forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
Ptr PGresult
resPtr <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection Ptr PGconn -> IO (Ptr PGresult)
f
if Ptr PGresult
resPtr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr PGresult -> Result
Result) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr PGresult -> IO ())
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 = 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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ 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 = forall b. Result -> (Ptr PGresult -> IO b) -> IO b
withResult Result
result Ptr PGresult -> IO CInt
f forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"enumFromResult") forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = 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 =
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr a
fp forall a b. (a -> b) -> a -> b
$ \Ptr a
p ->
do CString
cstr <- Ptr a -> IO CString
f Ptr a
p
if CString
cstr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do Int
l <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CString -> IO CSize
B.c_strlen CString
cstr
ForeignPtr Word8
fp' <- forall a. Ptr a -> IO () -> IO (ForeignPtr a)
FC.newForeignPtr (forall a b. Ptr a -> Ptr b
castPtr CString
cstr) IO ()
finalizer
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. a -> Maybe a
Just 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 = 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
_ <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn 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 forall a. Ptr a
nullPtr
Ptr CNoticeBuffer
nb <- forall a. MVar a -> a -> IO a
swapMVar MVar (Ptr CNoticeBuffer)
nbRef 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 forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
Ptr CNoticeBuffer
nb' <- IO (Ptr CNoticeBuffer)
c_malloc_noticebuffer
FunPtr NoticeReceiver
_ <- forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
conn 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 <- 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) =
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar (Ptr CNoticeBuffer)
nbRef 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 forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do
ForeignPtr Word8
fp <- forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr forall a. FunPtr (Ptr a -> IO ())
finalizerFree (forall a b. Ptr a -> Ptr b
castPtr Ptr PGnotice
np)
CSize
len <- Ptr PGnotice -> IO CSize
pgNoticePeekLen Ptr PGnotice
np
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
mkPS ForeignPtr Word8
fp Int
pgNoticeOffsetStr (forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
len)
newtype LoFd = LoFd CInt deriving (LoFd -> LoFd -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LoFd -> LoFd -> Bool
$c/= :: LoFd -> LoFd -> Bool
== :: LoFd -> LoFd -> Bool
$c== :: LoFd -> LoFd -> Bool
Eq, Eq LoFd
LoFd -> LoFd -> Bool
LoFd -> LoFd -> Ordering
LoFd -> LoFd -> LoFd
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LoFd -> LoFd -> LoFd
$cmin :: LoFd -> LoFd -> LoFd
max :: LoFd -> LoFd -> LoFd
$cmax :: LoFd -> LoFd -> LoFd
>= :: LoFd -> LoFd -> Bool
$c>= :: LoFd -> LoFd -> Bool
> :: LoFd -> LoFd -> Bool
$c> :: LoFd -> LoFd -> Bool
<= :: LoFd -> LoFd -> Bool
$c<= :: LoFd -> LoFd -> Bool
< :: LoFd -> LoFd -> Bool
$c< :: LoFd -> LoFd -> Bool
compare :: LoFd -> LoFd -> Ordering
$ccompare :: LoFd -> LoFd -> Ordering
Ord, Int -> LoFd -> ShowS
[LoFd] -> ShowS
LoFd -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [LoFd] -> ShowS
$cshowList :: [LoFd] -> ShowS
show :: LoFd -> [Char]
$cshow :: LoFd -> [Char]
showsPrec :: Int -> LoFd -> ShowS
$cshowsPrec :: Int -> LoFd -> ShowS
Show)
loMode :: IOMode -> CInt
loMode :: IOMode -> CInt
loMode = forall a. ToCInt a => a -> CInt
toCInt
toMaybeOid :: Oid -> IO (Maybe Oid)
toMaybeOid :: Oid -> IO (Maybe Oid)
toMaybeOid Oid
oid | Oid
oid forall a. Eq a => a -> a -> Bool
== Oid
invalidOid = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return (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 forall a. Ord a => a -> a -> Bool
< CInt
0 then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (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 forall a. Ord a => a -> a -> Bool
< CInt
0 then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just ())
{-# INLINE negError #-}
loCreat :: Connection -> IO (Maybe Oid)
loCreat :: Connection -> IO (Maybe Oid)
loCreat Connection
connection
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
Oid -> IO (Maybe Oid)
toMaybeOid 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
Oid -> IO (Maybe Oid)
toMaybeOid 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
filepath forall a b. (a -> b) -> a -> b
$ \CString
f -> do
Oid -> IO (Maybe Oid)
toMaybeOid 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
filepath forall a b. (a -> b) -> a -> b
$ \CString
f -> do
Oid -> IO (Maybe Oid)
toMaybeOid 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
filepath forall a b. (a -> b) -> a -> b
$ \CString
f -> do
CInt -> IO (Maybe ())
negError 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection 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 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
CInt
_ | IOMode
mode forall a. Eq a => a -> a -> Bool
/= IOMode
AppendMode -> forall (m :: * -> *) a. Monad m => a -> m a
return (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 (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
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
CInt
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
bytes forall a b. (a -> b) -> a -> b
$ \(CString
byteptr,Int
len) -> do
CInt -> IO (Maybe Int)
nonnegInt 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 (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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
Ptr Word8
buf <- 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 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxlen)
let len :: Int
len = forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len_
if Int
len forall a. Ord a => a -> a -> Bool
< Int
0
then do
forall a. Ptr a -> IO ()
free Ptr Word8
buf
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do
Ptr Word8
bufre <- forall a. Ptr a -> Int -> IO (Ptr a)
reallocBytes Ptr Word8
buf Int
len
ForeignPtr Word8
buffp <- forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr forall a. FunPtr (Ptr a -> IO ())
finalizerFree Ptr Word8
bufre
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. a -> Maybe a
Just 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
let d :: CInt
d = 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 forall a b. (a -> b) -> a -> b
$ 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)
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe Int)
nonnegInt 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe ())
negError 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 (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)
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe ())
negError 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
= forall b. Connection -> (Ptr PGconn -> IO b) -> IO b
withConn Connection
connection forall a b. (a -> b) -> a -> b
$ \Ptr PGconn
c -> do
CInt -> IO (Maybe ())
negError 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