Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.ContentsIndex
Database.ODBC.OdbcFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Wrappers for ODBC FFI functions, plus buffer marshaling.
Synopsis
data HandleObj = HandleObj
type Handle = Ptr HandleObj
data EnvObj = EnvObj
type EnvHandle = Ptr EnvObj
data ConnObj = ConnObj
type ConnHandle = Ptr ConnObj
data StmtObj = StmtObj
type StmtHandle = Ptr StmtObj
type WindowHandle = Ptr ()
data Buffer = Buffer
type BufferFPtr = ForeignPtr Buffer
type SizeFPtr = ForeignPtr SqlLen
data BindBuffer = BindBuffer {
bindBufPtr :: BufferFPtr
bindBufSzPtr :: SizeFPtr
bindBufSize :: SqlLen
}
type SqlInteger = Int32
type SqlUInteger = Word32
type SqlSmallInt = Int16
type SqlUSmallInt = Word16
type SqlLen = Int32
type SqlULen = Word32
type SqlReturn = SqlSmallInt
type SqlHandleType = SqlSmallInt
type SqlDataType = SqlSmallInt
type SqlCDataType = SqlSmallInt
type SqlParamDirection = SqlSmallInt
sqlDriverNoPrompt :: SqlUSmallInt
sqlNullTermedString :: SqlInteger
sqlNullData :: SqlLen
sqlTransCommit :: SqlSmallInt
sqlTransRollback :: SqlSmallInt
sqlAutoCommitOn :: SqlInteger
sqlAutoCommitOff :: SqlInteger
data OdbcException = OdbcException Int String String [OdbcException]
catchOdbc :: IO a -> (OdbcException -> IO a) -> IO a
throwOdbc :: OdbcException -> a
type MyCString = CString
type MyCStringLen = CStringLen
getDiagRec :: SqlReturn -> SqlHandleType -> Handle -> SqlSmallInt -> IO [OdbcException]
checkError :: SqlReturn -> SqlHandleType -> Handle -> IO ()
allocHdl :: Storable a => Handle -> SqlHandleType -> IO a
allocEnv :: IO EnvHandle
allocConn :: EnvHandle -> IO ConnHandle
allocStmt :: ConnHandle -> IO StmtHandle
freeHelper :: SqlHandleType -> Handle -> IO ()
freeEnv :: EnvHandle -> IO ()
freeConn :: ConnHandle -> IO ()
freeStmt :: StmtHandle -> IO ()
int2Ptr :: SqlInteger -> Ptr ()
setOdbcVer :: EnvHandle -> IO ()
connect :: ConnHandle -> String -> IO String
disconnect :: ConnHandle -> IO ()
prepareStmt :: StmtHandle -> String -> IO ()
executeStmt :: StmtHandle -> IO ()
closeCursor :: StmtHandle -> IO ()
rowCount :: StmtHandle -> IO Int
fetch :: StmtHandle -> IO Bool
moreResults :: StmtHandle -> IO Bool
commit :: ConnHandle -> IO ()
rollback :: ConnHandle -> IO ()
setAutoCommitOn :: ConnHandle -> IO ()
setAutoCommitOff :: ConnHandle -> IO ()
setTxnIsolation :: ConnHandle -> SqlInteger -> IO ()
getMaybeFromBuffer :: Storable a => Ptr SqlLen -> Ptr a -> (Ptr a -> SqlLen -> IO b) -> IO (Maybe b)
getDataStorable :: Storable a => StmtHandle -> Int -> SqlDataType -> Int -> (a -> b) -> IO (Maybe b)
getDataUtcTime :: StmtHandle -> Int -> IO (Maybe UTCTime)
getDataCStringLen :: StmtHandle -> Int -> IO (Maybe CStringLen)
getDataUTF8String :: StmtHandle -> Int -> IO (Maybe String)
getDataCString :: StmtHandle -> Int -> IO (Maybe String)
peekSmallInt :: Ptr a -> Int -> IO SqlSmallInt
peekUSmallInt :: Ptr a -> Int -> IO SqlUSmallInt
peekUInteger :: Ptr a -> Int -> IO SqlUInteger
readUtcTimeFromMemory :: Ptr Word8 -> IO UTCTime
bindColumnBuffer :: StmtHandle -> Int -> SqlDataType -> SqlLen -> IO BindBuffer
createEmptyBuffer :: SqlLen -> IO BindBuffer
testForNull :: BindBuffer -> (Ptr Buffer -> SqlLen -> IO a) -> IO (Maybe a)
getStorableFromBuffer :: Storable a => BindBuffer -> IO (Maybe a)
getCAStringFromBuffer :: BindBuffer -> IO (Maybe String)
getCWStringFromBuffer :: BindBuffer -> IO (Maybe String)
getUTF8StringFromBuffer :: BindBuffer -> IO (Maybe String)
getUtcTimeFromBuffer :: BindBuffer -> IO (Maybe UTCTime)
createBufferForStorable :: Storable a => Maybe a -> IO BindBuffer
createBufferHelper :: Storable a => a -> SqlLen -> IO BindBuffer
wrapSizedBuffer :: Ptr a -> SqlLen -> IO BindBuffer
bindParam :: StmtHandle -> Int -> SqlParamDirection -> SqlCDataType -> SqlDataType -> SqlULen -> SqlSmallInt -> BindBuffer -> IO ()
bindNull :: StmtHandle -> Int -> SqlParamDirection -> SqlCDataType -> SqlDataType -> IO BindBuffer
bindParamCStringLen :: StmtHandle -> Int -> SqlParamDirection -> Maybe CStringLen -> IO BindBuffer
bindEncodedString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> (String -> ((Ptr a, Int) -> IO BindBuffer) -> IO BindBuffer) -> IO BindBuffer
bindParamUTF8String :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> IO BindBuffer
bindParamCAString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> IO BindBuffer
bindParamCWString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> IO BindBuffer
pokeSmallInt :: Ptr a -> Int -> SqlSmallInt -> IO ()
pokeUSmallInt :: Ptr a -> Int -> SqlUSmallInt -> IO ()
pokeUInteger :: Ptr a -> Int -> SqlUInteger -> IO ()
writeUTCTimeToMemory :: Ptr Word8 -> UTCTime -> IO ()
makeUtcTimeBuffer :: UTCTime -> IO BindBuffer
makeUtcTimeStringBuffer :: UTCTime -> IO BindBuffer
bindParamUtcTime :: StmtHandle -> Int -> SqlParamDirection -> Maybe UTCTime -> IO BindBuffer
sizeOfMaybe :: forall a . Storable a => Maybe a -> Int
newtype OutParam a = OutParam a
newtype InOutParam a = InOutParam a
class OdbcBindBuffer a where
bindColBuffer :: StmtHandle -> Int -> Int -> a -> IO BindBuffer
getFromBuffer :: BindBuffer -> IO a
getData :: StmtHandle -> Int -> IO a
class OdbcBindParam a where
bindParamBuffer :: StmtHandle -> Int -> a -> IO BindBuffer
sqlAllocHandle :: SqlHandleType -> Handle -> Ptr Handle -> IO SqlReturn
sqlFreeHandle :: SqlSmallInt -> Handle -> IO SqlReturn
sqlGetDiagRec :: SqlHandleType -> Handle -> SqlSmallInt -> MyCString -> Ptr SqlInteger -> MyCString -> SqlSmallInt -> Ptr SqlSmallInt -> IO SqlReturn
sqlDriverConnect :: ConnHandle -> WindowHandle -> MyCString -> SqlSmallInt -> MyCString -> SqlSmallInt -> Ptr SqlSmallInt -> SqlUSmallInt -> IO SqlReturn
sqlDisconnect :: ConnHandle -> IO SqlReturn
sqlSetEnvAttr :: EnvHandle -> SqlInteger -> Ptr () -> SqlInteger -> IO SqlReturn
sqlSetConnectAttr :: ConnHandle -> SqlInteger -> Ptr () -> SqlInteger -> IO SqlReturn
sqlPrepare :: StmtHandle -> MyCString -> SqlInteger -> IO SqlReturn
sqlExecute :: StmtHandle -> IO SqlReturn
sqlCloseCursor :: StmtHandle -> IO SqlReturn
sqlRowCount :: StmtHandle -> Ptr SqlLen -> IO SqlReturn
sqlGetData :: StmtHandle -> SqlUSmallInt -> SqlDataType -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO SqlReturn
sqlBindCol :: StmtHandle -> SqlUSmallInt -> SqlDataType -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO SqlReturn
sqlFetch :: StmtHandle -> IO SqlReturn
sqlBindParameter :: StmtHandle -> SqlUSmallInt -> SqlParamDirection -> SqlCDataType -> SqlDataType -> SqlULen -> SqlSmallInt -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO SqlReturn
sqlMoreResults :: StmtHandle -> IO SqlReturn
sqlEndTran :: SqlSmallInt -> Handle -> SqlSmallInt -> IO SqlReturn
Documentation
data HandleObj
Constructors
HandleObj
type Handle = Ptr HandleObj
data EnvObj
Constructors
EnvObj
type EnvHandle = Ptr EnvObj
data ConnObj
Constructors
ConnObj
type ConnHandle = Ptr ConnObj
data StmtObj
Constructors
StmtObj
type StmtHandle = Ptr StmtObj
type WindowHandle = Ptr ()
data Buffer
Constructors
Buffer
type BufferFPtr = ForeignPtr Buffer
type SizeFPtr = ForeignPtr SqlLen
data BindBuffer
Constructors
BindBuffer
bindBufPtr :: BufferFPtr
bindBufSzPtr :: SizeFPtr
bindBufSize :: SqlLen
type SqlInteger = Int32
type SqlUInteger = Word32
type SqlSmallInt = Int16
type SqlUSmallInt = Word16
type SqlLen = Int32
type SqlULen = Word32
type SqlReturn = SqlSmallInt
type SqlHandleType = SqlSmallInt
type SqlDataType = SqlSmallInt
type SqlCDataType = SqlSmallInt
type SqlParamDirection = SqlSmallInt
sqlDriverNoPrompt :: SqlUSmallInt
sqlNullTermedString :: SqlInteger
sqlNullData :: SqlLen
sqlTransCommit :: SqlSmallInt
sqlTransRollback :: SqlSmallInt
sqlAutoCommitOn :: SqlInteger
sqlAutoCommitOff :: SqlInteger
data OdbcException
Constructors
OdbcException Int String String [OdbcException]
show/hide Instances
catchOdbc :: IO a -> (OdbcException -> IO a) -> IO a
throwOdbc :: OdbcException -> a
type MyCString = CString
type MyCStringLen = CStringLen
getDiagRec :: SqlReturn -> SqlHandleType -> Handle -> SqlSmallInt -> IO [OdbcException]
checkError :: SqlReturn -> SqlHandleType -> Handle -> IO ()
allocHdl :: Storable a => Handle -> SqlHandleType -> IO a
allocEnv :: IO EnvHandle
allocConn :: EnvHandle -> IO ConnHandle
allocStmt :: ConnHandle -> IO StmtHandle
freeHelper :: SqlHandleType -> Handle -> IO ()
freeEnv :: EnvHandle -> IO ()
freeConn :: ConnHandle -> IO ()
freeStmt :: StmtHandle -> IO ()
int2Ptr :: SqlInteger -> Ptr ()
setOdbcVer :: EnvHandle -> IO ()
connect :: ConnHandle -> String -> IO String
disconnect :: ConnHandle -> IO ()
prepareStmt :: StmtHandle -> String -> IO ()
executeStmt :: StmtHandle -> IO ()
closeCursor :: StmtHandle -> IO ()
rowCount :: StmtHandle -> IO Int
fetch :: StmtHandle -> IO Bool
Return True if there are more rows, False if end-of-data.
moreResults :: StmtHandle -> IO Bool
commit :: ConnHandle -> IO ()
rollback :: ConnHandle -> IO ()
setAutoCommitOn :: ConnHandle -> IO ()
setAutoCommitOff :: ConnHandle -> IO ()
setTxnIsolation :: ConnHandle -> SqlInteger -> IO ()
getMaybeFromBuffer :: Storable a => Ptr SqlLen -> Ptr a -> (Ptr a -> SqlLen -> IO b) -> IO (Maybe b)
getDataStorable :: Storable a => StmtHandle -> Int -> SqlDataType -> Int -> (a -> b) -> IO (Maybe b)
getDataUtcTime :: StmtHandle -> Int -> IO (Maybe UTCTime)
getDataCStringLen :: StmtHandle -> Int -> IO (Maybe CStringLen)
getDataUTF8String :: StmtHandle -> Int -> IO (Maybe String)
getDataCString :: StmtHandle -> Int -> IO (Maybe String)
peekSmallInt :: Ptr a -> Int -> IO SqlSmallInt
peekUSmallInt :: Ptr a -> Int -> IO SqlUSmallInt
peekUInteger :: Ptr a -> Int -> IO SqlUInteger
readUtcTimeFromMemory :: Ptr Word8 -> IO UTCTime
bindColumnBuffer :: StmtHandle -> Int -> SqlDataType -> SqlLen -> IO BindBuffer
createEmptyBuffer :: SqlLen -> IO BindBuffer
testForNull :: BindBuffer -> (Ptr Buffer -> SqlLen -> IO a) -> IO (Maybe a)
getStorableFromBuffer :: Storable a => BindBuffer -> IO (Maybe a)
getCAStringFromBuffer :: BindBuffer -> IO (Maybe String)
getCWStringFromBuffer :: BindBuffer -> IO (Maybe String)
getUTF8StringFromBuffer :: BindBuffer -> IO (Maybe String)
getUtcTimeFromBuffer :: BindBuffer -> IO (Maybe UTCTime)
createBufferForStorable :: Storable a => Maybe a -> IO BindBuffer
createBufferHelper :: Storable a => a -> SqlLen -> IO BindBuffer
wrapSizedBuffer :: Ptr a -> SqlLen -> IO BindBuffer
bindParam :: StmtHandle -> Int -> SqlParamDirection -> SqlCDataType -> SqlDataType -> SqlULen -> SqlSmallInt -> BindBuffer -> IO ()
bindNull :: StmtHandle -> Int -> SqlParamDirection -> SqlCDataType -> SqlDataType -> IO BindBuffer
bindParamCStringLen :: StmtHandle -> Int -> SqlParamDirection -> Maybe CStringLen -> IO BindBuffer
bindEncodedString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> (String -> ((Ptr a, Int) -> IO BindBuffer) -> IO BindBuffer) -> IO BindBuffer
bindParamUTF8String :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> IO BindBuffer
bindParamCAString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> IO BindBuffer
bindParamCWString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> IO BindBuffer
pokeSmallInt :: Ptr a -> Int -> SqlSmallInt -> IO ()
pokeUSmallInt :: Ptr a -> Int -> SqlUSmallInt -> IO ()
pokeUInteger :: Ptr a -> Int -> SqlUInteger -> IO ()
writeUTCTimeToMemory :: Ptr Word8 -> UTCTime -> IO ()
makeUtcTimeBuffer :: UTCTime -> IO BindBuffer
makeUtcTimeStringBuffer :: UTCTime -> IO BindBuffer
bindParamUtcTime :: StmtHandle -> Int -> SqlParamDirection -> Maybe UTCTime -> IO BindBuffer
sizeOfMaybe :: forall a . Storable a => Maybe a -> Int
newtype OutParam a
Constructors
OutParam a
newtype InOutParam a
Constructors
InOutParam a
class OdbcBindBuffer a where
Methods
bindColBuffer
:: StmtHandlestmt handle
-> Intcolumn position (1-indexed)
-> Intsize of result buffer (ignored when it can be inferred from type of a)
-> adummy value of the appropriate type (just to ensure we get the right class instance)
-> IO BindBufferreturns a BindBuffer object
getFromBuffer :: BindBuffer -> IO a
getData :: StmtHandle -> Int -> IO a
show/hide Instances
class OdbcBindParam a where
Methods
bindParamBuffer
:: StmtHandlestmt handle
-> Intparameter position (1-indexed)
-> avalue to write to buffer
-> IO BindBufferreturns a BindBuffer object
show/hide Instances
sqlAllocHandle :: SqlHandleType -> Handle -> Ptr Handle -> IO SqlReturn
sqlFreeHandle :: SqlSmallInt -> Handle -> IO SqlReturn
sqlGetDiagRec
:: SqlHandleTypeenum: which handle type is the next parameter?
-> Handlegeneric handle ptr
-> SqlSmallIntrow (or message) number
-> MyCStringOUT: state
-> Ptr SqlIntegerOUT: error number
-> MyCStringOUT: error message
-> SqlSmallIntIN: message buffer size
-> Ptr SqlSmallIntOUT: message length
-> IO SqlReturn
sqlDriverConnect
:: ConnHandle
-> WindowHandlejust pass nullPtr
-> MyCStringconnection string
-> SqlSmallIntconnection string size
-> MyCStringOUT: buffer for normalised connection string
-> SqlSmallIntbuffer size
-> Ptr SqlSmallIntOUT: length of returned string
-> SqlUSmallIntenum: should driver prompt user for missing info?
-> IO SqlReturn
sqlDisconnect :: ConnHandle -> IO SqlReturn
sqlSetEnvAttr
:: EnvHandleEnv Handle
-> SqlIntegerAttribute (enumeration)
-> Ptr ()value (cast to void*)
-> SqlInteger? - set to 0
-> IO SqlReturn
sqlSetConnectAttr
:: ConnHandleConnection Handle
-> SqlIntegerAttribute (enumeration)
-> Ptr ()value (cast to void*)
-> SqlInteger? - set to 0
-> IO SqlReturn
sqlPrepare :: StmtHandle -> MyCString -> SqlInteger -> IO SqlReturn
sqlExecute :: StmtHandle -> IO SqlReturn
sqlCloseCursor :: StmtHandle -> IO SqlReturn
sqlRowCount :: StmtHandle -> Ptr SqlLen -> IO SqlReturn
sqlGetData
:: StmtHandle
-> SqlUSmallIntcolumn position, 1-indexed
-> SqlDataTypeSQL data type: string, int, long, date, etc
-> Ptr Bufferoutput buffer
-> SqlLenoutput buffer size
-> Ptr SqlLenoutput data size, or -1 (SQL_NULL_DATA) for null
-> IO SqlReturn
sqlBindCol
:: StmtHandle
-> SqlUSmallIntcolumn position, 1-indexed
-> SqlDataTypeSQL data type: string, int, long, date, etc
-> Ptr Bufferoutput buffer
-> SqlLenoutput buffer size
-> Ptr SqlLenoutput data size, or -1 (SQL_NULL_DATA) for null
-> IO SqlReturn
sqlFetch :: StmtHandle -> IO SqlReturn
sqlBindParameter
:: StmtHandle
-> SqlUSmallIntposition, 1-indexed
-> SqlParamDirectiondirection: IN, OUT
-> SqlCDataTypeC data type: char, int, long, float, etc
-> SqlDataTypeSQL data type: string, int, long, date, etc
-> SqlULencol size (precision)
-> SqlSmallIntdecimal digits (scale)
-> Ptr Bufferinput+output buffer
-> SqlLenbuffer size
-> Ptr SqlLeninput+output data size, or -1 (SQL_NULL_DATA) for null
-> IO SqlReturn
sqlMoreResults :: StmtHandle -> IO SqlReturn
sqlEndTran :: SqlSmallInt -> Handle -> SqlSmallInt -> IO SqlReturn
Produced by Haddock version 0.7