module Database.PostgreSQL.PQTypes.Internal.C.Interface (
c_PQfreemem
, c_PQstatus
, c_PQerrorMessage
, c_PQsetClientEncoding
, c_PQsocket
, c_PQconsumeInput
, c_PQresultStatus
, c_PQresultErrorField
, c_PQresultErrorMessage
, c_PQntuples
, c_PQnfields
, c_PQcmdTuples
, c_PQgetisnull
, c_PQfname
, c_PQclear
, c_PQcancel
, c_PQconnectStart
, c_PQconnectPoll
, c_PQfinishPtr
, c_ptr_PQfinishPtr
, c_PQinitTypes
, c_PQregisterTypes
, c_PQparamExec
, c_PQparamCreate
, c_PQparamClear
, c_PQparamCount
, nullStringCStringLen
) where
import Foreign.C
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
import Foreign.Ptr
import System.Posix.Types
import qualified Control.Exception as E
import Database.PostgreSQL.PQTypes.Internal.C.Types
foreign import ccall unsafe "PQfreemem"
c_PQfreemem :: Ptr a -> IO ()
foreign import ccall unsafe "PQstatus"
c_PQstatus :: Ptr PGconn -> IO ConnStatusType
foreign import ccall unsafe "PQerrorMessage"
c_PQerrorMessage :: Ptr PGconn -> IO CString
foreign import ccall unsafe "PQsetClientEncoding"
c_PQsetClientEncoding :: Ptr PGconn -> CString -> IO CInt
foreign import ccall unsafe "PQsocket"
c_PQsocket :: Ptr PGconn -> IO Fd
foreign import ccall unsafe "PQconsumeInput"
c_PQconsumeInput :: Ptr PGconn -> IO CInt
foreign import ccall unsafe "PQresultStatus"
c_PQresultStatus :: Ptr PGresult -> IO ExecStatusType
foreign import ccall unsafe "PQresultErrorField"
c_PQresultErrorField :: Ptr PGresult -> ErrorField -> IO CString
foreign import ccall unsafe "PQresultErrorMessage"
c_PQresultErrorMessage :: Ptr PGresult -> IO CString
foreign import ccall unsafe "PQntuples"
c_PQntuples :: Ptr PGresult -> IO CInt
foreign import ccall unsafe "PQnfields"
c_PQnfields :: Ptr PGresult -> IO CInt
foreign import ccall unsafe "PQcmdTuples"
c_PQcmdTuples :: Ptr PGresult -> IO CString
foreign import ccall unsafe "PQgetisnull"
c_PQgetisnull :: Ptr PGresult -> CInt -> CInt -> IO CInt
foreign import ccall unsafe "PQfname"
c_PQfname :: Ptr PGresult -> CInt -> IO CString
foreign import ccall unsafe "PQclear"
c_PQclear :: Ptr PGresult -> IO ()
foreign import ccall unsafe "PQgetCancel"
c_PQgetCancel :: Ptr PGconn -> IO (Ptr PGcancel)
foreign import ccall unsafe "PQfreeCancel"
c_PQfreeCancel :: Ptr PGcancel -> IO ()
foreign import ccall unsafe "PQcancel"
c_rawPQcancel :: Ptr PGcancel -> CString -> CInt -> IO CInt
c_PQcancel :: Ptr PGconn -> IO (Maybe String)
c_PQcancel conn = E.bracket (c_PQgetCancel conn) c_PQfreeCancel $ \cancel -> do
allocaBytes errbufsize $ \errbuf -> do
c_rawPQcancel cancel errbuf (fromIntegral errbufsize) >>= \case
0 -> Just <$> peekCString errbuf
_ -> return Nothing
where
errbufsize :: Int
errbufsize = 256
foreign import ccall unsafe "PQconnectStart"
c_PQconnectStart :: CString -> IO (Ptr PGconn)
foreign import ccall unsafe "PQconnectPoll"
c_PQconnectPoll :: Ptr PGconn -> IO PostgresPollingStatusType
foreign import ccall unsafe "PQfinishPtr"
c_PQfinishPtr :: Ptr (Ptr PGconn) -> IO ()
foreign import ccall unsafe "&PQfinishPtr"
c_ptr_PQfinishPtr :: FunPtr (Ptr (Ptr PGconn) -> IO ())
foreign import ccall unsafe "PQinitTypes"
c_PQinitTypes :: Ptr PGconn -> IO ()
foreign import ccall unsafe "PQregisterTypes"
c_PQregisterTypes :: Ptr PGconn -> Ptr PGerror -> TypeClass -> Ptr PGregisterType -> CInt -> CInt -> IO CInt
foreign import ccall unsafe "PQparamCreate"
c_PQparamCreate :: Ptr PGconn -> Ptr PGerror -> IO (Ptr PGparam)
foreign import ccall unsafe "PQparamClear"
c_PQparamClear :: Ptr PGparam -> IO ()
foreign import ccall unsafe "PQparamCount"
c_PQparamCount :: Ptr PGparam -> IO CInt
foreign import ccall unsafe "&pqt_hs_null_string_ptr"
nullStringPtr :: Ptr CChar
nullStringCStringLen :: CStringLen
nullStringCStringLen = (nullStringPtr, 0)
foreign import ccall safe "PQparamExec"
c_rawPQparamExec :: Ptr PGconn -> Ptr PGerror -> Ptr PGparam -> CString -> ResultFormat -> IO (Ptr PGresult)
foreign import ccall unsafe "&PQclear"
c_ptr_PQclear :: FunPtr (Ptr PGresult -> IO ())
c_PQparamExec :: Ptr PGconn -> Ptr PGerror -> Ptr PGparam -> CString -> ResultFormat -> IO (ForeignPtr PGresult)
c_PQparamExec conn err param fmt mode = E.mask_ $ newForeignPtr c_ptr_PQclear
=<< c_rawPQparamExec conn err param fmt mode