Takusen-0.8.2: 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 ConnHdl = Ptr ConnObj
data ConnHandle = ConnHandle {
connHdl :: ConnHdl
connDbms :: String
}
data StmtObj = StmtObj
type StmtHdl = Ptr StmtObj
data StmtHandle = StmtHandle {
stmtHdl :: StmtHdl
stmtDbms :: String
}
type WindowHandle = Ptr ()
data Buffer = Buffer
type BufferFPtr = ForeignPtr Buffer
type SizeFPtr = ForeignPtr SqlLen
type MyCString = CString
type MyCStringLen = CStringLen
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
type SqlInfoType = SqlUSmallInt
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
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
freeHandle :: 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 ()
getInfoString :: ConnHandle -> SqlInfoType -> IO String
getInfoDbmsName :: ConnHandle -> IO String
getInfoDbmsVer :: ConnHandle -> IO String
getInfoDatabaseName :: ConnHandle -> IO String
getInfoDriverName :: ConnHandle -> IO String
getInfoDriverVer :: ConnHandle -> IO String
getNativeSql :: ConnHandle -> String -> IO String
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 -> Int -> IO BindBuffer
wrapSizedBuffer :: Ptr a -> SqlLen -> Int -> 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 -> Int -> IO BindBuffer
bindEncodedString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> (String -> ((Ptr a, Int) -> IO BindBuffer) -> IO BindBuffer) -> Int -> IO BindBuffer
bindParamUTF8String :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> Int -> IO BindBuffer
bindParamCAString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> Int -> IO BindBuffer
bindParamCWString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> Int -> 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 -> Int -> 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 :: ConnHdl -> WindowHandle -> MyCString -> SqlSmallInt -> MyCString -> SqlSmallInt -> Ptr SqlSmallInt -> SqlUSmallInt -> IO SqlReturn
sqlDisconnect :: ConnHdl -> IO SqlReturn
sqlSetEnvAttr :: EnvHandle -> SqlInteger -> Ptr () -> SqlInteger -> IO SqlReturn
sqlSetConnectAttr :: ConnHdl -> SqlInteger -> Ptr () -> SqlInteger -> IO SqlReturn
sqlPrepare :: StmtHdl -> MyCString -> SqlInteger -> IO SqlReturn
sqlBindParameter :: StmtHdl -> SqlUSmallInt -> SqlParamDirection -> SqlCDataType -> SqlDataType -> SqlULen -> SqlSmallInt -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO SqlReturn
sqlExecute :: StmtHdl -> IO SqlReturn
sqlNumResultCols :: StmtHdl -> Ptr SqlSmallInt -> IO SqlReturn
sqlRowCount :: StmtHdl -> Ptr SqlLen -> IO SqlReturn
sqlDescribeCol :: StmtHdl -> SqlUSmallInt -> MyCString -> SqlSmallInt -> Ptr SqlSmallInt -> Ptr SqlDataType -> Ptr SqlULen -> Ptr SqlSmallInt -> Ptr SqlSmallInt -> IO SqlReturn
sqlBindCol :: StmtHdl -> SqlUSmallInt -> SqlDataType -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO SqlReturn
sqlFetch :: StmtHdl -> IO SqlReturn
sqlGetData :: StmtHdl -> SqlUSmallInt -> SqlDataType -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO SqlReturn
sqlCloseCursor :: StmtHdl -> IO SqlReturn
sqlMoreResults :: StmtHdl -> IO SqlReturn
sqlEndTran :: SqlSmallInt -> Handle -> SqlSmallInt -> IO SqlReturn
sqlGetInfo :: ConnHdl -> SqlInfoType -> Ptr Buffer -> SqlSmallInt -> Ptr SqlSmallInt -> IO SqlReturn
sqlNativeSql :: ConnHdl -> MyCString -> SqlInteger -> MyCString -> SqlInteger -> Ptr SqlInteger -> IO SqlReturn
Documentation
data HandleObj
Constructors
HandleObj
type Handle = Ptr HandleObj
data EnvObj
Constructors
EnvObj
type EnvHandle = Ptr EnvObj
data ConnObj
Constructors
ConnObj
type ConnHdl = Ptr ConnObj
data ConnHandle
Constructors
ConnHandle
connHdl :: ConnHdl
connDbms :: String
data StmtObj
Constructors
StmtObj
type StmtHdl = Ptr StmtObj
data StmtHandle
Constructors
StmtHandle
stmtHdl :: StmtHdl
stmtDbms :: String
type WindowHandle = Ptr ()
data Buffer
Constructors
Buffer
type BufferFPtr = ForeignPtr Buffer
type SizeFPtr = ForeignPtr SqlLen
type MyCString = CString
type MyCStringLen = CStringLen
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
type SqlInfoType = SqlUSmallInt
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
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
freeHandle :: 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
Return True if there is another result-set to process. Presumably the StmtHandle is modified to reference the new result-set.
commit :: ConnHandle -> IO ()
rollback :: ConnHandle -> IO ()
setAutoCommitOn :: ConnHandle -> IO ()
setAutoCommitOff :: ConnHandle -> IO ()
setTxnIsolation :: ConnHandle -> SqlInteger -> IO ()
getInfoString :: ConnHandle -> SqlInfoType -> IO String
getInfoDbmsName :: ConnHandle -> IO String
getInfoDbmsVer :: ConnHandle -> IO String
getInfoDatabaseName :: ConnHandle -> IO String
getInfoDriverName :: ConnHandle -> IO String
getInfoDriverVer :: ConnHandle -> IO String
getNativeSql :: ConnHandle -> String -> IO String
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 -> Int -> IO BindBuffer
wrapSizedBuffer :: Ptr a -> SqlLen -> Int -> 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 -> Int -> IO BindBuffer
bindEncodedString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> (String -> ((Ptr a, Int) -> IO BindBuffer) -> IO BindBuffer) -> Int -> IO BindBuffer
bindParamUTF8String :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> Int -> IO BindBuffer
bindParamCAString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> Int -> IO BindBuffer
bindParamCWString :: StmtHandle -> Int -> SqlParamDirection -> Maybe String -> Int -> 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
show/hide Instances
OdbcBindParam (OutParam (Maybe Double))
OdbcBindParam (OutParam (Maybe Int))
OdbcBindParam (OutParam (Maybe String))
OdbcBindParam (OutParam (Maybe UTCTime))
newtype InOutParam a
Constructors
InOutParam a
show/hide Instances
OdbcBindParam (InOutParam (Maybe Double))
OdbcBindParam (InOutParam (Maybe Int))
OdbcBindParam (InOutParam (Maybe String))
OdbcBindParam (InOutParam (Maybe UTCTime))
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
OdbcBindBuffer (Maybe Double)
OdbcBindBuffer (Maybe Int)
OdbcBindBuffer (Maybe String)
OdbcBindBuffer (Maybe UTCTime)
class OdbcBindParam a where
Methods
bindParamBuffer
:: StmtHandlestmt handle
-> Intparameter position (1-indexed)
-> avalue to write to buffer
-> Intsize of buffer, for output. Value is ignored if input only (buffer will be sized to exactly hold input only) or size is fixed by type (e.g. Int, Double)
-> IO BindBufferreturns a BindBuffer object
show/hide Instances
OdbcBindParam (InOutParam (Maybe Double))
OdbcBindParam (InOutParam (Maybe Int))
OdbcBindParam (InOutParam (Maybe String))
OdbcBindParam (InOutParam (Maybe UTCTime))
OdbcBindParam (Maybe Double)
OdbcBindParam (Maybe Int)
OdbcBindParam (Maybe String)
OdbcBindParam (Maybe UTCTime)
OdbcBindParam (OutParam (Maybe Double))
OdbcBindParam (OutParam (Maybe Int))
OdbcBindParam (OutParam (Maybe String))
OdbcBindParam (OutParam (Maybe UTCTime))
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
:: ConnHdl
-> 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 :: ConnHdl -> IO SqlReturn
sqlSetEnvAttr
:: EnvHandleEnv Handle
-> SqlIntegerAttribute (enumeration)
-> Ptr ()value (cast to void*)
-> SqlInteger? - set to 0
-> IO SqlReturn
sqlSetConnectAttr
:: ConnHdlConnection Handle
-> SqlIntegerAttribute (enumeration)
-> Ptr ()value (cast to void*)
-> SqlInteger? - set to 0
-> IO SqlReturn
sqlPrepare :: StmtHdl -> MyCString -> SqlInteger -> IO SqlReturn
sqlBindParameter
:: StmtHdl
-> 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
sqlExecute :: StmtHdl -> IO SqlReturn
sqlNumResultCols :: StmtHdl -> Ptr SqlSmallInt -> IO SqlReturn
sqlRowCount :: StmtHdl -> Ptr SqlLen -> IO SqlReturn
sqlDescribeCol
:: StmtHdl
-> SqlUSmallIntposition, 1-indexed
-> MyCStringbuffer for column name
-> SqlSmallIntsize of column name buffer
-> Ptr SqlSmallIntsize of column name output string
-> Ptr SqlDataTypeSQL data type: string, int, long, date, etc
-> Ptr SqlULencol size (precision)
-> Ptr SqlSmallIntdecimal digits (scale)
-> Ptr SqlSmallIntnullable: SQL_NO_NULLS, SQL_NULLABLE, or SQL_NULLABLE_UNKNOWN
-> IO SqlReturn
sqlBindCol
:: StmtHdl
-> 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 :: StmtHdl -> IO SqlReturn
sqlGetData
:: StmtHdl
-> 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
sqlCloseCursor :: StmtHdl -> IO SqlReturn
sqlMoreResults :: StmtHdl -> IO SqlReturn
sqlEndTran :: SqlSmallInt -> Handle -> SqlSmallInt -> IO SqlReturn
sqlGetInfo
:: ConnHdl
-> SqlInfoTypeinformation type
-> Ptr Bufferoutput buffer
-> SqlSmallIntoutput buffer size
-> Ptr SqlSmallIntoutput data size, or -1 (SQL_NULL_DATA) for null
-> IO SqlReturn
sqlNativeSql
:: ConnHdl
-> MyCStringsql text in
-> SqlIntegersize of sql text
-> MyCStringbuffer for output text
-> SqlIntegersize of output buffer
-> Ptr SqlIntegersize of text in output buffer
-> IO SqlReturn
Produced by Haddock version 0.7