 | Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. | Contents | Index |
|
| Database.ODBC.OdbcFunctions | | Portability | non-portable | | Stability | experimental | | Maintainer | oleg@pobox.com, alistair@abayley.org |
|
|
|
|
|
| Description |
| Wrappers for ODBC FFI functions, plus buffer marshaling.
|
|
| Synopsis |
|
|
|
| Documentation |
|
| data HandleObj |
|
|
| type Handle = Ptr HandleObj |
|
| data EnvObj |
|
|
| type EnvHandle = Ptr EnvObj |
|
| data ConnObj |
|
|
| type ConnHdl = Ptr ConnObj |
|
| data ConnHandle |
| Constructors | | ConnHandle | | | connHdl :: ConnHdl | | | connDbms :: String | |
|
|
|
|
| data StmtObj |
|
|
| type StmtHdl = Ptr StmtObj |
|
| data StmtHandle |
| Constructors | | StmtHandle | | | stmtHdl :: StmtHdl | | | stmtDbms :: String | |
|
|
|
|
| type WindowHandle = Ptr () |
|
| data Buffer |
|
|
| type BufferFPtr = ForeignPtr Buffer |
|
| type SizeFPtr = ForeignPtr SqlLen |
|
| type MyCString = CString |
|
| type MyCStringLen = CStringLen |
|
| data BindBuffer |
|
|
| 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 | | 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 | | Instances | |
|
|
| newtype InOutParam a |
| Constructors | | Instances | |
|
|
| class OdbcBindBuffer a where |
| | Methods | | bindColBuffer | | :: StmtHandle | stmt handle
| | -> Int | column position (1-indexed)
| | -> Int | size of result buffer (ignored when it can be inferred from type of a)
| | -> a | dummy value of the appropriate type (just to ensure we get the right class instance)
| | -> IO BindBuffer | returns a BindBuffer object
|
| | | getFromBuffer :: BindBuffer -> IO a | | | getData :: StmtHandle -> Int -> IO a |
| | Instances | |
|
|
| class OdbcBindParam a where |
| | Methods | | bindParamBuffer | | :: StmtHandle | stmt handle
| | -> Int | parameter position (1-indexed)
| | -> a | value to write to buffer
| | -> Int | size 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 BindBuffer | returns a BindBuffer object
|
|
| | Instances | |
|
|
| sqlAllocHandle :: SqlHandleType -> Handle -> Ptr Handle -> IO SqlReturn |
|
| sqlFreeHandle :: SqlSmallInt -> Handle -> IO SqlReturn |
|
| sqlGetDiagRec |
|
|
| sqlDriverConnect |
|
|
| sqlDisconnect :: ConnHdl -> IO SqlReturn |
|
| sqlSetEnvAttr |
|
|
| sqlSetConnectAttr |
|
|
| sqlPrepare :: StmtHdl -> MyCString -> SqlInteger -> IO SqlReturn |
|
| sqlBindParameter |
| :: StmtHdl | | | -> SqlUSmallInt | position, 1-indexed
| | -> SqlParamDirection | direction: IN, OUT
| | -> SqlCDataType | C data type: char, int, long, float, etc
| | -> SqlDataType | SQL data type: string, int, long, date, etc
| | -> SqlULen | col size (precision)
| | -> SqlSmallInt | decimal digits (scale)
| | -> Ptr Buffer | input+output buffer
| | -> SqlLen | buffer size
| | -> Ptr SqlLen | input+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 |
|
|
| sqlBindCol |
|
|
| sqlFetch :: StmtHdl -> IO SqlReturn |
|
| sqlGetData |
|
|
| sqlCloseCursor :: StmtHdl -> IO SqlReturn |
|
| sqlMoreResults :: StmtHdl -> IO SqlReturn |
|
| sqlEndTran :: SqlSmallInt -> Handle -> SqlSmallInt -> IO SqlReturn |
|
| sqlGetInfo |
|
|
| sqlNativeSql |
|
|
| Produced by Haddock version 0.7 |