[New Haddock doc files for new modules. alistair@abayley.org**20080304172541] { addfile ./doc/html/Database-InternalEnumerator.html hunk ./doc/html/Database-InternalEnumerator.html 1 + + +Database.InternalEnumerator
 Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.ContentsIndex
Database.InternalEnumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Contents
Session object. +
Exceptions and handlers +
Description

This is the interface between the middle Enumerator layer and the + low-level, Database-specific layer. This file is not exported to the end user. +

Only the programmer for a new back-end needs to consult this file. +

Synopsis
class ISession sess where
disconnect :: sess -> IO ()
beginTransaction :: sess -> IsolationLevel -> IO ()
commit :: sess -> IO ()
rollback :: sess -> IO ()
newtype ConnectA sess = ConnectA (IO sess)
class ISession sess => Statement stmt sess q | stmt sess -> q where
makeQuery :: sess -> stmt -> IO q
class ISession sess => Command stmt sess where
executeCommand :: sess -> stmt -> IO Int
class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> result where
inquire :: inquirykey -> sess -> IO result
newtype PreparationA sess stmt = PreparationA (sess -> IO stmt)
class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> bo where
bindRun :: sess -> stmt -> [BindA sess stmt bo] -> (bound_stmt -> IO a) -> IO a
destroyStmt :: sess -> stmt -> IO ()
newtype BindA sess stmt bo = BindA (sess -> stmt -> bo)
class ISession sess => DBBind a sess stmt bo | stmt -> bo where
bindP :: a -> BindA sess stmt bo
data IsolationLevel
= ReadUncommitted
| ReadCommitted
| RepeatableRead
| Serialisable
| Serializable
type Position = Int
class ISession sess => IQuery q sess b | q -> sess, q -> b where
fetchOneRow :: q -> IO Bool
currentRowNum :: q -> IO Int
freeBuffer :: q -> b -> IO ()
destroyQuery :: q -> IO ()
class DBType a q b | q -> b where
allocBufferFor :: a -> q -> Position -> IO b
fetchCol :: q -> b -> IO a
throwIfDBNull :: Monad m => m (RowNum, ColNum) -> m (Maybe a) -> m a
data DBException
= DBError SqlState Int String
| DBFatal SqlState Int String
| DBUnexpectedNull RowNum ColNum
| DBNoData
throwDB :: DBException -> a
type ColNum = Int
type RowNum = Int
type SqlState = (SqlStateClass, SqlStateSubClass)
type SqlStateClass = String
type SqlStateSubClass = String
Session object. +
class ISession sess where

The ISession class describes a database session to a particular + DBMS. Oracle has its own Session object, SQLite has its own + session object (which maintains the connection handle to the database + engine and other related stuff). Session objects for different databases + normally have different types -- yet they all belong to the class ISession + so we can do generic operations like commit, execDDL, etc. + in a database-independent manner. +

Session objects per se are created by database connection/login functions. +

The class ISession is thus an interface between low-level (and + database-specific) code and the Enumerator, database-independent + code. + The ISession class is NOT visible to the end user -- neither the class, + nor any of its methods. +

The ISession class describes the mapping from connection object to + the session object. The connection object is created by the end user + (and this is how the end user tells which particular back end he wants). + The session object is not accessible by the end user in any way. + Even the type of the session object should be hidden! +

Methods
disconnect :: sess -> IO ()
beginTransaction :: sess -> IsolationLevel -> IO ()
commit :: sess -> IO ()
rollback :: sess -> IO ()
show/hide Instances
newtype ConnectA sess
A wrapper around the action to open the database. That wrapper is not + exported to the end user. The only reason for the wrapper is to + guarantee that the only thing to do with the result of + connect function is to pass it out + directly to withSession. +
Constructors
ConnectA (IO sess)
show/hide Instances
??? sess => Typeable (ConnectA sess)
class ISession sess => Statement stmt sess q | stmt sess -> q where
Statement defines the API for query objects i.e. + which types can be queries. +
Methods
makeQuery :: sess -> stmt -> IO q
show/hide Instances
Statement BoundStmt Session Query
Statement BoundStmt Session Query
Statement BoundStmt Session Query
Statement BoundStmt Session Query
Statement PreparedStmtObj Session Query
Statement PreparedStmtObj Session Query
Statement PreparedStmtObj Session Query
Statement QueryString Session Query
Statement QueryString Session Query
Statement QueryString Session Query
Statement QueryString Session Query
Statement QueryString Session Query
Statement QueryStringTuned Session Query
Statement QueryStringTuned Session Query
Statement QueryStringTuned Session Query
Statement StmtBind Session Query
Statement StmtBind Session Query
Statement String Session Query
Statement String Session Query
Statement String Session Query
Statement String Session Query
Statement (RefCursor StmtHandle) Session Query
Statement (RefCursor String) Session Query
Statement (NextResultSet mark PreparedStmtObj) Session Query
Statement (NextResultSet mark PreparedStmtObj) Session Query
class ISession sess => Command stmt sess where
Command is not a query: command deletes or updates rows, creates/drops + tables, or changes database state. + executeCommand returns the number of affected rows (or 0 if DDL i.e. not DML). +
Methods
executeCommand :: sess -> stmt -> IO Int
show/hide Instances
class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> result where
Methods
inquire :: inquirykey -> sess -> IO result
show/hide Instances
newtype PreparationA sess stmt

This type is not visible to the end user (cf. ConnectA). It forms a private + `communication channel' between Database.Enumerator and a back end. +

Why don't we make a user-visible class with a prepare method? + Because it means to standardize the preparation method signature + across all databases. Some databases need more parameters, some + fewer. There may be several statement preparation functions within one + database. So, instead of standardizing the signature of the + preparation function, we standardize on the _result_ of that + function. To be more precise, we standardize on the properties of the + result: whatever it is, the eventual prepared statement should be + suitable to be passed to bindRun. +

Constructors
PreparationA (sess -> IO stmt)
class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> bo where
Methods
bindRun :: sess -> stmt -> [BindA sess stmt bo] -> (bound_stmt -> IO a) -> IO a
destroyStmt :: sess -> stmt -> IO ()
show/hide Instances
IPrepared PreparedStmtObj Session BoundStmt BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
newtype BindA sess stmt bo
The binding object (bo) below is very abstract, on purpose. + It may be |IO a|, it may be String, it may be a function, etc. + The binding object can hold the result of marshalling, + or bo can hold the current counter, etc. + Different databases do things very differently: + compare PostgreSQL and the Stub (which models Oracle). +
Constructors
BindA (sess -> stmt -> bo)
class ISession sess => DBBind a sess stmt bo | stmt -> bo where
The class DBBind is not used by the end-user. + It is used to tie up low-level database access and the enumerator. + A database-specific library must provide a set of instances for DBBind. + The latter are the dual of DBType. +
Methods
bindP :: a -> BindA sess stmt bo
This is really just a wrapper that lets us write lists of + heterogenous bind values e.g. [bindP "string", bindP (0::Int), ...] +
show/hide Instances
DBBind (Maybe a) Session PreparedStmtObj BindObj => DBBind a Session PreparedStmtObj BindObj
DBBind (Maybe a) Session PreparedStmtObj BindObj => DBBind a Session PreparedStmtObj BindObj
DBBind (Maybe a) Session PreparedStmtObj BindObj => DBBind a Session PreparedStmtObj BindObj
DBBind (Maybe a) Session PreparedStmtObj BindObj => DBBind a Session PreparedStmtObj BindObj
DBBind (Maybe CalendarTime) Session PreparedStmtObj BindObj
DBBind (Maybe CalendarTime) Session PreparedStmtObj BindObj
DBBind (Maybe Double) Session PreparedStmtObj BindObj
DBBind (Maybe Double) Session PreparedStmtObj BindObj
DBBind (Maybe Double) Session PreparedStmtObj BindObj
DBBind (Maybe Double) Session PreparedStmtObj BindObj
DBBind (Maybe Float) Session PreparedStmtObj BindObj
DBBind (Maybe Int) Session PreparedStmtObj BindObj
DBBind (Maybe Int) Session PreparedStmtObj BindObj
DBBind (Maybe Int) Session PreparedStmtObj BindObj
DBBind (Maybe Int) Session PreparedStmtObj BindObj
DBBind (Maybe Int64) Session PreparedStmtObj BindObj
DBBind (Maybe Int64) Session PreparedStmtObj BindObj
DBBind (Maybe String) Session PreparedStmtObj BindObj
DBBind (Maybe String) Session PreparedStmtObj BindObj
DBBind (Maybe String) Session PreparedStmtObj BindObj
DBBind (Maybe String) Session PreparedStmtObj BindObj
DBBind (Maybe UTCTime) Session PreparedStmtObj BindObj
DBBind (Maybe UTCTime) Session PreparedStmtObj BindObj
DBBind (Maybe UTCTime) Session PreparedStmtObj BindObj
DBBind (Maybe UTCTime) Session PreparedStmtObj BindObj
Show a => DBBind (Maybe a) Session PreparedStmtObj BindObj
Show a => DBBind (Maybe a) Session PreparedStmtObj BindObj
Show a => DBBind (Maybe a) Session PreparedStmtObj BindObj
Show a => DBBind (Maybe a) Session PreparedStmtObj BindObj
DBBind (Out (Maybe Double)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe Int)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe StmtHandle)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe String)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe UTCTime)) Session PreparedStmtObj BindObj
Show a => DBBind (Out (Maybe a)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe a)) Session PreparedStmtObj BindObj => DBBind (Out a) Session PreparedStmtObj BindObj
data IsolationLevel
Constructors
ReadUncommitted
ReadCommitted
RepeatableRead
Serialisable
Serializablefor alternative spellers +
show/hide Instances
type Position = Int
class ISession sess => IQuery q sess b | q -> sess, q -> b where

The class IQuery describes the class of query objects. Each + database (that is, each Session object) has its own Query object. + We may assume that a Query object includes (at least, conceptually) + a (pointer to) a Session object, so a Query object determines the + Session object. + A back-end provides an instance (or instances) of IQuery. + The end user never seens the IQuery class (let alone its methods). +

Can a session have several types of query objects? + Let's assume that it can: but a statement plus the session uniquely + determine the query, +

Note that we explicitly use IO monad because we will have to explicitly + do FFI. +

Methods
fetchOneRow :: q -> IO Bool
currentRowNum :: q -> IO Int
freeBuffer :: q -> b -> IO ()
destroyQuery :: q -> IO ()
show/hide Instances
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
class DBType a q b | q -> b where

A 'buffer' means a column buffer: a data structure that points to a + block of memory allocated for the values of one particular + column. Since a query normally fetches a row of several columns, we + typically deal with a list of column buffers. Although the column data + are typed (e.g., Integer, CalendarDate, etc), column buffers hide that + type. Think of the column buffer as Dynamics. The class DBType below + describes marshalling functions, to fetch a typed value out of the + 'untyped' columnBuffer. +

Different DBMS's (that is, different session objects) have, in + general, columnBuffers of different types: the type of Column Buffer + is specific to a database. + So, ISession (m) uniquely determines the buffer type (b)?? + Or, actually, a query uniquely determines the buffer. +

The class DBType is not used by the end-user. + It is used to tie up low-level database access and the enumerator. + A database-specific library must provide a set of instances for DBType. +

Methods
allocBufferFor :: a -> q -> Position -> IO b
fetchCol :: q -> b -> IO a
show/hide Instances
DBType (Maybe a) Query ColumnBuffer => DBType a Query ColumnBuffer
DBType (Maybe a) Query ColumnBuffer => DBType a Query ColumnBuffer
DBType (Maybe a) Query ColumnBuffer => DBType a Query ColumnBuffer
DBType (Maybe a) Query ColumnBuffer => DBType a Query ColumnBuffer
DBType (Maybe a) Query ColumnBuffer => DBType a Query ColumnBuffer
DBType (Maybe CalendarTime) Query ColumnBuffer
DBType (Maybe CalendarTime) Query ColumnBuffer
DBType (Maybe CalendarTime) Query ColumnBuffer
DBType (Maybe CalendarTime) Query ColumnBuffer
DBType (Maybe Double) Query ColumnBuffer
DBType (Maybe Double) Query ColumnBuffer
DBType (Maybe Double) Query ColumnBuffer
DBType (Maybe Double) Query ColumnBuffer
DBType (Maybe Double) Query ColumnBuffer
DBType (Maybe Float) Query ColumnBuffer
DBType (Maybe Int) Query ColumnBuffer
DBType (Maybe Int) Query ColumnBuffer
DBType (Maybe Int) Query ColumnBuffer
DBType (Maybe Int) Query ColumnBuffer
DBType (Maybe Int) Query ColumnBuffer
DBType (Maybe Int64) Query ColumnBuffer
DBType (Maybe Int64) Query ColumnBuffer
DBType (Maybe String) Query ColumnBuffer
DBType (Maybe String) Query ColumnBuffer
DBType (Maybe String) Query ColumnBuffer
DBType (Maybe String) Query ColumnBuffer
DBType (Maybe String) Query ColumnBuffer
DBType (Maybe UTCTime) Query ColumnBuffer
DBType (Maybe UTCTime) Query ColumnBuffer
DBType (Maybe UTCTime) Query ColumnBuffer
DBType (Maybe UTCTime) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
DBType (RefCursor StmtHandle) Query ColumnBuffer
DBType (RefCursor String) Query ColumnBuffer
throwIfDBNull :: Monad m => m (RowNum, ColNum) -> m (Maybe a) -> m a
Used by instances of DBType to throw an exception + when a null (Nothing) is returned. + Will work for any type, as you pass the fetch action in the fetcher arg. +
Exceptions and handlers +
data DBException
Constructors
DBError SqlState Int StringDBMS error message. +
DBFatal SqlState Int String
DBUnexpectedNull RowNum ColNumthe iteratee function used for queries accepts both nullable (Maybe) and + non-nullable types. If the query itself returns a null in a column where a + non-nullable type was specified, we can't handle it, so DBUnexpectedNull is thrown. +
DBNoDataThrown by cursor functions if you try to fetch after the end. +
show/hide Instances
throwDB :: DBException -> a
Throw a DBException. It's just a type-specific throwDyn. +
type ColNum = Int
type RowNum = Int
type SqlState = (SqlStateClass, SqlStateSubClass)
type SqlStateClass = String
type SqlStateSubClass = String
Produced by Haddock version 0.7
addfile ./doc/html/Database-ODBC-Enumerator.html hunk ./doc/html/Database-ODBC-Enumerator.html 1 + + +Database.ODBC.Enumerator
 Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.ContentsIndex
Database.ODBC.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
ODBC implementation of Database.Enumerator. +
Documentation
data Session
show/hide Instances
ISession Session
Typeable Session
Command BoundStmt Session
Command QueryString Session
Command StmtBind Session
Command String Session
IQuery Query Session ColumnBuffer
Statement BoundStmt Session Query
Statement PreparedStmtObj Session Query
Statement QueryString Session Query
Statement StmtBind Session Query
Statement String Session Query
DBBind (Maybe a) Session PreparedStmtObj BindObj => DBBind a Session PreparedStmtObj BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
DBBind (Maybe Double) Session PreparedStmtObj BindObj
DBBind (Maybe Int) Session PreparedStmtObj BindObj
DBBind (Maybe String) Session PreparedStmtObj BindObj
DBBind (Maybe UTCTime) Session PreparedStmtObj BindObj
Show a => DBBind (Maybe a) Session PreparedStmtObj BindObj
connect :: String -> ConnectA Session
prepareStmt :: QueryString -> PreparationA Session PreparedStmtObj
preparePrefetch :: Int -> QueryString -> PreparationA Session PreparedStmtObj
prepareQuery :: QueryString -> PreparationA Session PreparedStmtObj
prepareLargeQuery :: Int -> QueryString -> PreparationA Session PreparedStmtObj
prepareCommand :: QueryString -> PreparationA Session PreparedStmtObj
sql :: String -> QueryString
sqlbind :: String -> [BindA Session PreparedStmtObj BindObj] -> StmtBind
prefetch :: Int -> String -> [BindA Session PreparedStmtObj BindObj] -> StmtBind
cmdbind :: String -> [BindA Session PreparedStmtObj BindObj] -> StmtBind
module Database.Enumerator
Produced by Haddock version 0.7
addfile ./doc/html/Database-ODBC-OdbcFunctions.html hunk ./doc/html/Database-ODBC-OdbcFunctions.html 1 + + +Database.ODBC.OdbcFunctions
 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
addfile ./doc/html/Foreign-C-UTF8.html hunk ./doc/html/Foreign-C-UTF8.html 1 + + +Foreign.C.UTF8
 Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.ContentsIndex
Foreign.C.UTF8
Portabilityportable
Stabilityexperimental
Maintaineralistair@abayley.org
Description

Marshall Haskell Strings to and from UTF8-encoded CStrings. + This module's code is inspired by John Meacham's UTF8 en- & de-coders, + and also those found in the HXT library (module Text.XML.HXT.DOM.Unicode). +

Note that the -Len functions all return the length in bytes, + not Chars (this is more useful, as you are most likely to want + to pass the length to an FFI function, which is most likely + expecting the length in bytes). If you want the length in Chars, + well, you have the original String, so... +

Synopsis
peekUTF8String :: CString -> IO String
peekUTF8StringLen :: CStringLen -> IO String
newUTF8String :: String -> IO CString
withUTF8String :: String -> (CString -> IO a) -> IO a
withUTF8StringLen :: String -> (CStringLen -> IO a) -> IO a
toUTF8String :: String -> String
fromUTF8String :: String -> String
lengthUTF8 :: String -> Int
fromUTF8 :: [Word8] -> String
toUTF8 :: String -> [Word8]
Documentation
peekUTF8String :: CString -> IO String
Analogous to peekCString. Converts UTF8 CString to String. +
peekUTF8StringLen :: CStringLen -> IO String
Analogous to peekCStringLen. Converts UTF8 CString to String. + The resulting String will end either when len bytes + have been converted, or when a NULL is found. +
newUTF8String :: String -> IO CString
Analogous to newCString. Creates UTF8 encoded CString. +
withUTF8String :: String -> (CString -> IO a) -> IO a
Analogous to withCString. Creates UTF8 encoded CString. +
withUTF8StringLen :: String -> (CStringLen -> IO a) -> IO a
Analogous to withCStringLen. + The length returned is in bytes (encoding units), not chars. +
toUTF8String :: String -> String
Convert a Haskell String into a UTF8 String, where each UTF8 byte + is represented by its Char equivalent i.e. only chars 0-255 are used. + The resulting String can be marshalled to CString directly i.e. with + a Latin-1 encoding. +
fromUTF8String :: String -> String
Convert a String that was marshalled from a CString without + any decoder applied. This might be useful if the client encoding + is unknown, and the user code must convert. + We assume that the UTF8 CString was marshalled as if Latin-1 + i.e. all chars are in the range 0-255. +
lengthUTF8 :: String -> Int
fromUTF8 :: [Word8] -> String
Convert UTF-8 to Unicode. +
toUTF8 :: String -> [Word8]
Convert Unicode characters to UTF-8. +
Produced by Haddock version 0.7
}