|
Database.PostgreSQL.PGFunctions | Portability | non-portable | Stability | experimental | Maintainer | oleg@pobox.com, alistair@abayley.org |
|
|
|
|
|
Description |
Simple wrappers for PostgreSQL functions (FFI) plus middle-level
wrappers (in the second part of this file)
|
|
Synopsis |
|
data DBHandleStruct = PGconn | | type DBHandle = Ptr DBHandleStruct | | data StmtStruct = PGresult | | type ResultSetHandle = Ptr StmtStruct | | type Oid = CUInt | | type Format = CInt | | type Void = () | | type ParamLen = CInt | | data PGException = PGException Int String | | catchPG :: IO a -> (PGException -> IO a) -> IO a | | throwPG :: Integral a => a -> String -> any | | rethrowPG :: PGException -> any | | cStr :: CStringLen -> CString | | cStrLen :: CStringLen -> CInt | | fPQconnectdb :: CString -> IO DBHandle | | fPQfinish :: DBHandle -> IO () | | fPQreset :: DBHandle -> IO () | | fPQdb :: DBHandle -> CString | | type ConnStatusType = CInt | | fPQstatus :: DBHandle -> IO ConnStatusType | | fPQerrorMessage :: DBHandle -> IO CString | | type NoticeReceiver = Ptr () -> ResultSetHandle -> IO () | | type NoticeProcessor = Ptr () -> CString -> IO () | | mkNoticeReceiver :: NoticeReceiver -> IO (FunPtr NoticeReceiver) | | mkNoticeProcessor :: NoticeProcessor -> IO (FunPtr NoticeProcessor) | | fPQsetNoticeReceiver :: DBHandle -> FunPtr NoticeReceiver -> Ptr () -> IO (FunPtr NoticeReceiver) | | fPQsetNoticeProcessor :: DBHandle -> FunPtr NoticeProcessor -> Ptr () -> IO (FunPtr NoticeProcessor) | | fPQexecParams :: DBHandle -> CString -> CInt -> Ptr Oid -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle | | fPQprepare :: DBHandle -> CString -> CString -> CInt -> Ptr Oid -> IO ResultSetHandle | | fPQexecPrepared :: DBHandle -> CString -> CInt -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle | | fPQresultStatus :: ResultSetHandle -> IO ExecStatusType | | type ExecStatusType = CInt | | fPQresultErrorMessage :: ResultSetHandle -> IO CString | | fPQclear :: ResultSetHandle -> IO () | | fPQntuples :: ResultSetHandle -> IO CInt | | fPQnfields :: ResultSetHandle -> IO CInt | | fPQfname :: ResultSetHandle -> CInt -> IO CString | | fPQfformat :: ResultSetHandle -> CInt -> IO CInt | | fPQftype :: ResultSetHandle -> CInt -> IO Oid | | fPQgetvalue :: ResultSetHandle -> CInt -> CInt -> IO (Ptr Word8) | | fPQgetisnull :: ResultSetHandle -> CInt -> CInt -> IO CInt | | fPQgetlength :: ResultSetHandle -> CInt -> CInt -> IO CInt | | fPQcmdStatus :: ResultSetHandle -> IO CString | | fPQcmdTuples :: ResultSetHandle -> IO CString | | fPQoidValue :: ResultSetHandle -> IO Oid | | fPQputCopyData :: DBHandle -> Ptr Word8 -> CInt -> IO CInt | | fPQputCopyEnd :: DBHandle -> CString -> IO CInt | | fPQgetResult :: DBHandle -> IO ResultSetHandle | | type PGVerbosity = CInt | | fPQsetErrorVerbosity :: DBHandle -> PGVerbosity -> IO PGVerbosity | | getError :: DBHandle -> IO String | | openDb :: String -> IO DBHandle | | closeDb :: DBHandle -> IO () | | class PGType a where | | | pgZeroDate :: UTCTime | | toPGTime :: UTCTime -> Double | | fromPGTime :: Double -> UTCTime | | data PGBindVal = PGBindVal {} | | newBinaryValue :: (Storable a, PGType b) => (b -> a) -> b -> IO (Ptr Word8) | | peekValueRev :: (Storable a, PGType b) => b -> (a -> b) -> Ptr Word8 -> IO b | | reverseBytes :: Int -> Ptr Word8 -> Ptr Word8 -> IO () | | reverseBytes' :: Int -> Ptr Word8 -> Ptr Word8 -> IO () | | toCInt :: Int -> CInt | | fromCInt :: CInt -> Int | | toCInt16 :: Int16 -> CShort | | fromCInt16 :: CShort -> Int16 | | toCInt32 :: Int32 -> CInt | | fromCInt32 :: CInt -> Int32 | | toCInt64 :: Int64 -> CLLong | | fromCInt64 :: CLLong -> Int64 | | toCChar :: Char -> CChar | | fromCChar :: CChar -> Char | | toCDouble :: Double -> CDouble | | fromCDouble :: CDouble -> Double | | toCFloat :: Float -> CFloat | | fromCFloat :: CFloat -> Float | | check'stmt :: DBHandle -> ExecStatusType -> ResultSetHandle -> IO ResultSetHandle | | stmtPrepare :: DBHandle -> String -> String -> [Oid] -> IO String | | nqExec :: DBHandle -> String -> IO (String, String, Oid) | | execCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid) | | execPreparedCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid) | | stmtExecImm :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int) | | stmtExecImm0 :: DBHandle -> String -> IO (ResultSetHandle, Int) | | stmtExec0 :: DBHandle -> String -> IO (ResultSetHandle, Int) | | stmtExec0t :: DBHandle -> String -> IO (ResultSetHandle, Int) | | stmtExec :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int) | | execPrepared :: DBHandle -> String -> [PGBindVal] -> CInt -> IO (ResultSetHandle, Int) | | prepare'n'exec :: DBHandle -> String -> String -> [PGBindVal] -> IO (ResultSetHandle, Int) | | stmtFinalise :: ResultSetHandle -> IO () | | colValPtr :: ResultSetHandle -> Int -> Int -> IO (Ptr Word8) | | colVal :: (Read a, PGType a) => ResultSetHandle -> Int -> Int -> IO a | | colValString :: ResultSetHandle -> Int -> Int -> IO String | | colValInt :: ResultSetHandle -> Int -> Int -> IO Int | | colValInt64 :: ResultSetHandle -> Int -> Int -> IO Int64 | | colValDouble :: ResultSetHandle -> Int -> Int -> IO Double | | colValFloat :: ResultSetHandle -> Int -> Int -> IO Float | | colValUTCTime :: ResultSetHandle -> Int -> Int -> IO UTCTime | | colValNull :: ResultSetHandle -> Int -> Int -> IO Bool | | sbph :: String -> Int -> Bool -> String -> String | | nqCopyIn_buflen :: Int | | nqCopyIn :: DBHandle -> String -> Handle -> IO () |
|
|
Documentation |
|
data DBHandleStruct |
|
|
type DBHandle = Ptr DBHandleStruct |
|
data StmtStruct |
|
|
type ResultSetHandle = Ptr StmtStruct |
|
type Oid = CUInt |
|
type Format = CInt |
|
type Void = () |
|
type ParamLen = CInt |
|
data PGException |
Constructors | | Instances | |
|
|
catchPG :: IO a -> (PGException -> IO a) -> IO a |
|
throwPG :: Integral a => a -> String -> any |
|
rethrowPG :: PGException -> any |
|
cStr :: CStringLen -> CString |
|
cStrLen :: CStringLen -> CInt |
|
fPQconnectdb :: CString -> IO DBHandle |
|
fPQfinish :: DBHandle -> IO () |
|
fPQreset :: DBHandle -> IO () |
|
fPQdb :: DBHandle -> CString |
|
type ConnStatusType = CInt |
|
fPQstatus :: DBHandle -> IO ConnStatusType |
|
fPQerrorMessage :: DBHandle -> IO CString |
|
type NoticeReceiver = Ptr () -> ResultSetHandle -> IO () |
|
type NoticeProcessor = Ptr () -> CString -> IO () |
|
mkNoticeReceiver :: NoticeReceiver -> IO (FunPtr NoticeReceiver) |
|
mkNoticeProcessor :: NoticeProcessor -> IO (FunPtr NoticeProcessor) |
|
fPQsetNoticeReceiver :: DBHandle -> FunPtr NoticeReceiver -> Ptr () -> IO (FunPtr NoticeReceiver) |
|
fPQsetNoticeProcessor :: DBHandle -> FunPtr NoticeProcessor -> Ptr () -> IO (FunPtr NoticeProcessor) |
|
fPQexecParams :: DBHandle -> CString -> CInt -> Ptr Oid -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle |
|
fPQprepare :: DBHandle -> CString -> CString -> CInt -> Ptr Oid -> IO ResultSetHandle |
|
fPQexecPrepared :: DBHandle -> CString -> CInt -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle |
|
fPQresultStatus :: ResultSetHandle -> IO ExecStatusType |
|
type ExecStatusType = CInt |
|
fPQresultErrorMessage :: ResultSetHandle -> IO CString |
|
fPQclear :: ResultSetHandle -> IO () |
|
fPQntuples :: ResultSetHandle -> IO CInt |
|
fPQnfields :: ResultSetHandle -> IO CInt |
|
fPQfname :: ResultSetHandle -> CInt -> IO CString |
|
fPQfformat :: ResultSetHandle -> CInt -> IO CInt |
|
fPQftype :: ResultSetHandle -> CInt -> IO Oid |
|
fPQgetvalue :: ResultSetHandle -> CInt -> CInt -> IO (Ptr Word8) |
|
fPQgetisnull :: ResultSetHandle -> CInt -> CInt -> IO CInt |
|
fPQgetlength :: ResultSetHandle -> CInt -> CInt -> IO CInt |
|
fPQcmdStatus :: ResultSetHandle -> IO CString |
|
fPQcmdTuples :: ResultSetHandle -> IO CString |
|
fPQoidValue :: ResultSetHandle -> IO Oid |
|
fPQputCopyData :: DBHandle -> Ptr Word8 -> CInt -> IO CInt |
|
fPQputCopyEnd :: DBHandle -> CString -> IO CInt |
|
fPQgetResult :: DBHandle -> IO ResultSetHandle |
|
type PGVerbosity = CInt |
|
fPQsetErrorVerbosity :: DBHandle -> PGVerbosity -> IO PGVerbosity |
|
getError :: DBHandle -> IO String |
|
openDb :: String -> IO DBHandle |
|
closeDb :: DBHandle -> IO () |
|
class PGType a where |
| Methods | | | Instances | |
|
|
pgZeroDate :: UTCTime |
|
toPGTime :: UTCTime -> Double |
|
fromPGTime :: Double -> UTCTime |
|
data PGBindVal |
|
|
newBinaryValue :: (Storable a, PGType b) => (b -> a) -> b -> IO (Ptr Word8) |
|
peekValueRev :: (Storable a, PGType b) => b -> (a -> b) -> Ptr Word8 -> IO b |
|
reverseBytes :: Int -> Ptr Word8 -> Ptr Word8 -> IO () |
|
reverseBytes' :: Int -> Ptr Word8 -> Ptr Word8 -> IO () |
|
toCInt :: Int -> CInt |
|
fromCInt :: CInt -> Int |
|
toCInt16 :: Int16 -> CShort |
|
fromCInt16 :: CShort -> Int16 |
|
toCInt32 :: Int32 -> CInt |
|
fromCInt32 :: CInt -> Int32 |
|
toCInt64 :: Int64 -> CLLong |
|
fromCInt64 :: CLLong -> Int64 |
|
toCChar :: Char -> CChar |
|
fromCChar :: CChar -> Char |
|
toCDouble :: Double -> CDouble |
|
fromCDouble :: CDouble -> Double |
|
toCFloat :: Float -> CFloat |
|
fromCFloat :: CFloat -> Float |
|
check'stmt :: DBHandle -> ExecStatusType -> ResultSetHandle -> IO ResultSetHandle |
|
stmtPrepare :: DBHandle -> String -> String -> [Oid] -> IO String |
|
nqExec :: DBHandle -> String -> IO (String, String, Oid) |
|
execCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid) |
|
execPreparedCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid) |
|
stmtExecImm :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int) |
|
stmtExecImm0 :: DBHandle -> String -> IO (ResultSetHandle, Int) |
|
stmtExec0 :: DBHandle -> String -> IO (ResultSetHandle, Int) |
|
stmtExec0t :: DBHandle -> String -> IO (ResultSetHandle, Int) |
|
stmtExec :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int) |
|
execPrepared :: DBHandle -> String -> [PGBindVal] -> CInt -> IO (ResultSetHandle, Int) |
|
prepare'n'exec :: DBHandle -> String -> String -> [PGBindVal] -> IO (ResultSetHandle, Int) |
|
stmtFinalise :: ResultSetHandle -> IO () |
|
colValPtr :: ResultSetHandle -> Int -> Int -> IO (Ptr Word8) |
Column numbers are zero-indexed, so subtract one
from given index (we present a one-indexed interface).
So are the row numbers.
|
|
colVal :: (Read a, PGType a) => ResultSetHandle -> Int -> Int -> IO a |
|
colValString :: ResultSetHandle -> Int -> Int -> IO String |
|
colValInt :: ResultSetHandle -> Int -> Int -> IO Int |
|
colValInt64 :: ResultSetHandle -> Int -> Int -> IO Int64 |
|
colValDouble :: ResultSetHandle -> Int -> Int -> IO Double |
|
colValFloat :: ResultSetHandle -> Int -> Int -> IO Float |
|
colValUTCTime :: ResultSetHandle -> Int -> Int -> IO UTCTime |
|
colValNull :: ResultSetHandle -> Int -> Int -> IO Bool |
|
sbph :: String -> Int -> Bool -> String -> String |
|
nqCopyIn_buflen :: Int |
|
nqCopyIn :: DBHandle -> String -> Handle -> IO () |
|
Produced by Haddock version 0.7 |