[docs/html: update Haddock docs. alistair@abayley.org**20080711100521] { hunk ./doc/html/Control-Exception-MonadIO.html 22 ->Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. MonadIO m => MonadIO m => :: m a -> (Exception -> m a) -> m a :: m a -> (Exception -> m a) -> m a :: (Exception -> Maybe b) -> m a -> (b -> m a) -> m a :: (Exception -> Maybe b) -> m a -> (b -> m a) -> m a IO IO (ReaderT a m) (ReaderT a m) m => m b -> m (Either Exception b) m => m b -> m (Either Exception b) m => (Exception -> Maybe b) -> m b1 -> m (Either b b1) m => (Exception -> Maybe b) -> m b1 -> m (Either b b1)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.class ISession sess data ConnectA sess :: (Typeable a, :: (Typeable a, sess) => sess) => mark sess a) -> IO a mark sess a) -> IO a :: (Typeable a, :: (Typeable a, sess) => sess) => mark sess a) -> IO (a, mark sess a) -> IO (a, :: :: :: :: :: (MonadReader s (ReaderT s IO), :: (MonadReader s (ReaderT s IO), :: :: :: :: :: :: mark s Int mark s Int :: :: Int String Int String Int String Int String -> String -> String m => String -> m => String -> m => Int -> m a -> ( m => Int -> m a -> ( m => Int -> m a -> m a m => Int -> m a -> m anewtypetype ColNum = Inttype RowNum = Inttype SqlState = (SqlStateClass, SqlStateSubClass)type SqlStateClass = Stringtype SqlStateSubClass = Stringdata mark stmt = PreparedStmt stmt mark stmt :: (Typeable a, :: (Typeable a, stmt sess bstmt bo) => stmt sess bstmt bo) => :: (Typeable a, :: (Typeable a, mark stmt -> [ mark stmt -> [class ISession sess => Statement stmt sess q | stmt sess -> qclass ISession sess => Command stmt sess class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> resultdata PreparationA sess stmtclass ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> bodata BindA sess stmt boclass ISession sess => DBBind a sess stmt bo | stmt -> bo where
bindP :: a -> BindA sess stmt bo
:: :: a sess stmt bo => a -> a sess stmt bo => a -> class ISession sess => IQuery q sess b | q -> sess, q -> b where
currentRowNum :: q -> IO Int
:: ( :: ( mark sess) q i seed b, mark sess) q i seed b, class DBType a q b | q -> b seedType = Either seedType seedType seedType = Either seedType seedType :: :: q sess b => q -> IO Int q sess b => q -> IO Int mark s Bool mark s Bool :: (Typeable a, :: (Typeable a, mark sess) q i seed b, mark sess) q i seed b, type Position = Int :: Maybe a -> a -> a :: Maybe a -> a -> a :: Monad m => :: Monad m => :: Monad m => :: Monad m => sqlbind "select ..." [bindP ..., bindP ...] +> sqlbind "select ?, ... where col = ? and ..." [bindP ..., bindP ...] hunk ./doc/html/Database-Enumerator.html 1271 -> prefetch 100 "select ..." [bindP ..., bindP ...] +> prefetch 100 "select ?, ... where col = ? and ..." [bindP ..., bindP ...] hunk ./doc/html/Database-Enumerator.html 1279 -> cmdbind "insert into ..." [bindP ..., bindP ...] +> cmdbind "insert into ... values (?, ?, ...)" [bindP ..., bindP ...] hunk ./doc/html/Database-Enumerator.html 1289 -> let stmt = prepareQuery (sql "select ...") +> let stmt = prepareQuery (sql "select ? ...") hunk ./doc/html/Database-Enumerator.html 1348 ->(( sess, ??? a sess) => Functor ( sess, ??? a sess) => Functor ((( sess, ??? a sess) => Monad ( sess, ??? a sess) => Monad ((( sess, ??? a sess) => MonadFix ( sess, ??? a sess) => MonadFix ((( sess, ??? a sess) => MonadIO ( sess, ??? a sess) => MonadIO (class ISession sess

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! +

show/hide Instances
data 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. +
show/hide Instances
??? sess => Typeable (ConnectA sess)
:: (Typeable a, :: (Typeable a, sess) => sess) => mark sess a) -> IO a mark sess a) -> IO a :: (Typeable a, :: (Typeable a, sess) => sess) => mark sess a) -> IO (a, mark sess a) -> IO (a, :: :: :: :: :: (MonadReader s (ReaderT s IO), :: (MonadReader s (ReaderT s IO), :: :: Show Enum IsolationLevelEq IsolationLevelOrd IsolationLevelShow :: :: :: :: mark s Int mark s Int :: :: Int String Int String Int String Int String Show Show Typeable Typeable -> String -> String m => String -> m => String -> m => Int -> m a -> ( m => Int -> m a -> ( m => Int -> m a -> m a m => Int -> m a -> m aPreparing and Binding -type ColNum = Inttype RowNum = Intnewtype
type PreparedStmt mark stmtSqlState = (SqlStateClass, SqlStateSubClass)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.TypeableTypeable String String String String (Maybe a) (Maybe a) PreparedStmtObj BindObj => PreparedStmtObj BindObj => DBBind (Maybe Double) Session PreparedStmtObj BindObj :: String -> QueryString :: String -> [ :: String -> [ :: Int -> String -> [ :: Int -> String -> [ :: String -> [ :: String -> [Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. = Ptr = Ptr = Ptr = Ptr ConnHdl = Ptr ConnObjStmtHdl = Ptr StmtObj = Ptr () = Ptr () = ForeignPtr = ForeignPtr = ForeignPtr = ForeignPtr type MyCString = CString = Int32 = Word32 = Word32 = Int16 = Int16 = Word16 = Word16 = Int32 = Int32 = Word32 = Word32typeSqlInfoType = SqlUSmallInt -> IO a) -> IO atypeMyCString = CString -> IO () :: Storable a => :: Storable a => -> IO a -> IO a :: IO :: IO -> IO -> IO -> IO -> IO freeHelperfreeHandle -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> Ptr () -> Ptr () -> IO () -> IO () -> String -> IOString -> String -> IO String -> IO () -> IO () -> String -> IO () -> String -> IO () -> IO () -> IO () -> IO () -> IO () -> IOInt -> IO Int -> IOBool -> IO Bool -> IOBool -> IO Bool -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () :: Storable a => Ptr :: Storable a => Ptr -> Ptr a -> (Ptr a -> -> Ptr a -> (Ptr a -> -> IO b) -> IO (Maybe b) -> IO b) -> IO (Maybe b) :: Storable a => :: Storable a => -> Int -> -> Int -> -> Int -> (a -> b) -> IO (Maybe b) -> Int -> (a -> b) -> IO (Maybe b) -> Int -> IO (MaybeUTCTime) -> Int -> IO (Maybe UTCTime) -> Int -> IO (MaybeCStringLen) -> Int -> IO (Maybe CStringLen) -> Int -> IO (MaybeString) -> Int -> IO (Maybe String) -> Int -> IO (MaybeString) -> Int -> IO (Maybe String) :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: PtrWord8 -> IOUTCTime :: Ptr Word8 -> IO UTCTime -> Int -> -> Int -> -> IO -> IO -> IO -> IO -> (Ptr -> (Ptr -> IO a) -> IO (Maybe a) -> IO a) -> IO (Maybe a) :: Storable a => :: Storable a => -> IO (Maybe a) -> IO (Maybe a) -> IO (MaybeString) -> IO (Maybe String) -> IO (MaybeString) -> IO (Maybe String) -> IO (MaybeString) -> IO (Maybe String) -> IO (MaybeUTCTime) -> IO (Maybe UTCTime) :: Storable a => Maybe a -> IO :: Storable a => Maybe a -> IO :: Storable a => a -> :: Storable a => a -> -> IO -> Int -> IO :: Ptr a -> :: Ptr a -> -> IO -> Int -> IO -> Int -> -> Int -> -> IO () -> IO () -> Int -> -> Int -> -> IO -> IO -> Int -> -> Int -> -> MaybeCStringLen -> IO -> Maybe CStringLen -> Int -> IO -> Int -> -> Int -> -> MaybeString -> (String -> ((Ptr a, Int) -> IO -> Maybe String -> (String -> ((Ptr a, Int) -> IO ) -> IO) -> IO ) -> IO) -> Int -> IO -> Int -> -> Int -> -> MaybeString -> IO -> Maybe String -> Int -> IO -> Int -> -> Int -> -> MaybeString -> IO -> Maybe String -> Int -> IO -> Int -> -> Int -> -> MaybeString -> IO -> Maybe String -> Int -> IO :: Ptr a -> Int -> :: Ptr a -> Int -> -> IO () -> IO () :: Ptr a -> Int -> :: Ptr a -> Int -> -> IO () -> IO () :: Ptr a -> Int -> :: Ptr a -> Int -> -> IO () -> IO () :: PtrWord8 -> UTCTime -> IO () :: Ptr Word8 -> UTCTime -> IO () :: UTCTime -> IO :: UTCTime -> IO :: UTCTime -> IO :: UTCTime -> IO -> Int -> -> Int -> -> MaybeUTCTime -> IO -> Maybe UTCTime -> IO a . Storable a => Maybe a -> Int a . Storable a => Maybe a -> Int -> Int -> Int -> a -> IO -> Int -> Int -> a -> IO -> IO a -> IO a -> Int -> IO a -> Int -> IO a -> Int -> a -> IO -> Int -> a -> Int -> IO -> Ptr -> Ptr -> IO -> IO -> IO -> IO -> Ptr -> Ptr -> Ptr -> Ptr -> IO -> IO :: ConnHandle :: ConnHdl -> Ptr -> Ptr -> IO -> IO :: ConnHandle -> IO :: ConnHdl -> IO -> Ptr () -> -> Ptr () -> -> IO -> IO :: ConnHandle :: ConnHdl -> Ptr () -> -> Ptr () -> -> IO -> IO :: StmtHandle :: StmtHdl -> IO -> IO SqlReturn = Ptr () = ForeignPtr = ForeignPtr = ForeignPtr = ForeignPtr type MyCString = CString = Int32 = Word32 = Word32 = Int16 = Int16 = Word16 = Word16 = Int32 = Int32 = Word32 = Word32typeSqlInfoType = SqlUSmallInt -> IO a) -> IO atypeMyCString = CString -> IO () :: Storable a => :: Storable a => -> IO a -> IO a :: IO :: IO -> IO -> IO -> IO -> IO freeHelperfreeHandle -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> Ptr () -> Ptr () -> IO () -> IO () -> String -> IOString -> String -> IO String -> IO () -> IO () -> String -> IO () -> String -> IO () -> IO () -> IO () -> IO () -> IO () -> IOInt -> IO Int -> IOBool -> IO BoolReturn True if there are more rows, False if end-of-data. +>Return True if there are more rows, False if end-of-data. hunk ./doc/html/Database-ODBC-OdbcFunctions.html 3344 -> -> IOBool -> IO Bool -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () -> IO () :: Storable a => Ptr :: Storable a => Ptr -> Ptr a -> (Ptr a -> -> Ptr a -> (Ptr a -> -> IO b) -> IO (Maybe b) -> IO b) -> IO (Maybe b) :: Storable a => :: Storable a => -> Int -> -> Int -> -> Int -> (a -> b) -> IO (Maybe b) -> Int -> (a -> b) -> IO (Maybe b) -> Int -> IO (MaybeUTCTime) -> Int -> IO (Maybe UTCTime) -> Int -> IO (MaybeCStringLen) -> Int -> IO (Maybe CStringLen) -> Int -> IO (MaybeString) -> Int -> IO (Maybe String) -> Int -> IO (MaybeString) -> Int -> IO (Maybe String) :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: Ptr a -> Int -> IO :: PtrWord8 -> IOUTCTime :: Ptr Word8 -> IO UTCTime -> Int -> -> Int -> -> IO -> IO -> IO -> IO -> (Ptr -> (Ptr -> IO a) -> IO (Maybe a) -> IO a) -> IO (Maybe a) :: Storable a => :: Storable a => -> IO (Maybe a) -> IO (Maybe a) -> IO (MaybeString) -> IO (Maybe String) -> IO (MaybeString) -> IO (Maybe String) -> IO (MaybeString) -> IO (Maybe String) -> IO (MaybeUTCTime) -> IO (Maybe UTCTime) :: Storable a => Maybe a -> IO :: Storable a => Maybe a -> IO :: Storable a => a -> :: Storable a => a -> -> IO -> Int -> IO :: Ptr a -> :: Ptr a -> -> IO -> Int -> IO -> Int -> -> Int -> -> IO () -> IO () -> Int -> -> Int -> -> IO -> IO -> Int -> -> Int -> -> MaybeCStringLen -> IO -> Maybe CStringLen -> Int -> IO -> Int -> -> Int -> -> MaybeString -> (String -> ((Ptr a, Int) -> IO -> Maybe String -> (String -> ((Ptr a, Int) -> IO ) -> IO) -> IO ) -> IO) -> Int -> IO -> Int -> -> Int -> -> MaybeString -> IO -> Maybe String -> Int -> IO -> Int -> -> Int -> -> MaybeString -> IO -> Maybe String -> Int -> IO -> Int -> -> Int -> -> MaybeString -> IO -> Maybe String -> Int -> IO :: Ptr a -> Int -> :: Ptr a -> Int -> -> IO () -> IO () :: Ptr a -> Int -> :: Ptr a -> Int -> -> IO () -> IO () :: Ptr a -> Int -> :: Ptr a -> Int -> -> IO () -> IO () :: PtrWord8 -> UTCTime -> IO () :: Ptr Word8 -> UTCTime -> IO () :: UTCTime -> IO :: UTCTime -> IO :: UTCTime -> IO :: UTCTime -> IO -> Int -> -> Int -> -> MaybeUTCTime -> IO -> Maybe UTCTime -> IO a . Storable a => Maybe a -> Int a . Storable a => Maybe a -> Int-> Int-> Int-> Int-> Int-> IO-> IO -> IO a -> IO a -> Int -> IO a -> Int -> IO a (MaybeDouble) (Maybe Double) (MaybeInt) (Maybe Int) (MaybeString) (Maybe String) (MaybeUTCTime) (Maybe UTCTime)-> Int-> Int-> IO-> Int (InOutParam (Maybe Double)) (MaybeInt) (InOutParam (Maybe String)) (MaybeString) (InOutParam (Maybe UTCTime)) (MaybeUTCTime) (Maybe Double) -> Ptr -> Ptr -> IO -> IO -> IO -> IO -> Ptr-> Ptr -> Ptr-> Ptr -> IO-> IO :: ConnHandle:: ConnHdl-> Ptr-> Ptr -> IO-> IO :: ConnHandle -> IO :: ConnHdl -> IO -> Ptr ()-> Ptr ()-> IO-> IO :: ConnHandle:: ConnHdl-> Ptr ()-> Ptr ()-> IO-> IO :: StmtHandle :: StmtHdl -> IO -> IO SqlReturn :: StmtHandle -> IO :: StmtHdl -> IO sqlCloseCursor :: StmtHandle -> IOsqlNumResultCols :: StmtHdl -> Ptr SqlSmallInt -> IO :: StmtHandle -> Ptr :: StmtHdl -> Ptr -> IO -> IO sqlGetDatasqlDescribeCol:: StmtHandle:: StmtHdlcolumn position, 1-indexed +>position, 1-indexed hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5219 ->-> -> MyCString
Constructorstype SqlStateClass = String
type PreparedStmt stmtSqlStateSubClass = String
Preparing and Binding +
data PreparedStmt mark stmt
:: (Typeable a, :: (Typeable a, => => :: (Typeable a, :: (Typeable a, -> [-> [class ISession sess => Statement stmt sess q | stmt sess -> q seedType = Either seedType seedType :: :: q sess b => q -> IOInt q sess b => q -> IO Int String) Query ColumnBuffer String) Query ColumnBuffer String) String) mark s Bool mark s BoolDBNoData exception is thrown. + a DBNoData exception is thrown. hunk ./doc/html/Database-Enumerator.html 5518 ->:: (Typeable a, :: (Typeable a, mark sess) q i seed b, mark sess) q i seed b, :: Maybe a:: Maybe a :: Monad m => :: Monad m => :: Monad m => :: Monad m => - -Database.InternalEnumerator
Statement defines the API for query objects i.e. + which types can be queries. +
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
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). +
show/hide Instances
Command BoundStmt Session
Command BoundStmt Session
Command BoundStmt Session
Command BoundStmt Session
Command CommandBind Session
Command CommandBind Session
Command QueryString Session
Command QueryString Session
Command QueryString Session
Command QueryString Session
Command QueryString Session
Command QueryStringTuned Session
Command StmtBind Session
Command StmtBind Session
Command String Session
Command String Session
Command String Session
Command String Session
class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> result
show/hide Instances
data 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. +

class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> bo
show/hide Instances
IPrepared PreparedStmtObj Session BoundStmt BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
IPrepared PreparedStmtObj Session BoundStmt BindObj
data 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). +
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 Double)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe Int)) 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 String)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe UTCTime)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe UTCTime)) Session PreparedStmtObj BindObj
Show a => DBBind (Out (Maybe a)) 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
DBBind (Out (Maybe a)) Session PreparedStmtObj BindObj => DBBind (Out a) Session PreparedStmtObj BindObj
:: :: a sess stmt bo => a -> a sess stmt bo => a -> 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
currentRowNum :: q -> IO Int
show/hide Instances
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
IQuery Query Session ColumnBuffer
:: (:: ( mark sess) q i seed b, mark sess) q i seed b, class DBType a q b | q -> b

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. +

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
seedType = Either seedType seedType type Position = Int
 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
rmfile ./doc/html/Database-InternalEnumerator.html hunk ./doc/html/Database-ODBC-Enumerator.html 22 ->Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.
DBBind (Maybe Int) Session PreparedStmtObj BindObj
(Maybe Double) (Maybe String) (Maybe Int) (Maybe UTCTime) Show a => (Maybe String) (Maybe a) (Maybe UTCTime) (Out (Maybe Double)) Show a => (Maybe (Out (Maybe Int)) 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 :: String -> :: String -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: String -> QueryString
newtype Out a
Constructors
Out a
show/hide Instances
DBBind (Out (Maybe Double)) Session PreparedStmtObj BindObj
DBBind (Out (Maybe Int)) 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 = Ptr ConnObj = ConnHandle {
connHdl :: ConnHdlconnDbms :: String
}
data = Ptr StmtObj = StmtHandle {
stmtHdl :: StmtHdlstmtDbms :: String
}
type MyCStringLen = CStringLen
= Int32
Int String String [ Int String String [ :: IO a -> ( :: IO a -> ( -> IO a) -> IO a
type MyCStringLen = CStringLen
-> IO [ -> IO [ -> 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
sqlBindParameter :: StmtHdl -> SqlUSmallInt -> SqlParamDirection -> SqlCDataType -> SqlDataType -> SqlULen -> SqlSmallInt -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO :: StmtHandle -> IO :: StmtHdl -> IO sqlCloseCursor :: StmtHandle -> IO sqlNumResultCols :: StmtHdl -> Ptr SqlSmallInt -> IO :: StmtHandle -> Ptr :: StmtHdl -> Ptr -> IO -> IO sqlGetData :: StmtHandlesqlDescribeCol :: StmtHdl -> -> MyCString -> SqlSmallInt -> Ptr SqlSmallInt -> Ptr -> Ptr Buffer -> SqlLen -> Ptr SqlLen -> IO -> Ptr SqlULen -> Ptr SqlSmallInt -> Ptr SqlSmallInt -> IO :: StmtHandle :: StmtHdl -> Ptr -> Ptr -> Ptr -> Ptr -> IO -> IO :: StmtHandle -> IO :: StmtHdl -> IO sqlBindParameter :: StmtHandlesqlGetData :: StmtHdl -> SqlParamDirection -> SqlCDataType -> SqlULen -> SqlSmallInt -> Ptr -> Ptr -> Ptr -> Ptr -> IO -> IO SqlReturn
sqlCloseCursor :: StmtHdl -> IO :: StmtHandle -> IO :: StmtHdl -> IO -> IO -> IO SqlReturn
sqlGetInfo :: ConnHdl -> SqlInfoType -> Ptr Buffer -> SqlSmallInt -> Ptr SqlSmallInt -> IO SqlReturn
sqlNativeSql :: ConnHdl -> MyCString -> SqlInteger -> MyCString -> SqlInteger -> Ptr SqlInteger -> IO = Ptr = Ptr = Ptr = Ptr ConnHdl = Ptr ConnObj
data = Ptr ConnObj
Constructors
ConnHandle
connHdl :: ConnHdl
connDbms :: String
StmtHdl = Ptr StmtObj
data = Ptr StmtObj
Constructors
StmtHandle
stmtHdl :: StmtHdl
stmtDbms :: String
= Ptr ()
type MyCStringLen = CStringLen
= Int32
Int String String [ Int String String [Show Show Typeable Typeable :: IO a -> ( :: IO a -> ( -> IO a) -> IO a
type MyCStringLen = CStringLen
-> IO [ -> IO [ -> IO ()
Return True if there is another result-set to process. + Presumably the StmtHandle is modified to reference the + new result-set. +
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
show/hide Instances
OdbcBindParam (OutParam (Maybe Double))
OdbcBindParam (OutParam (Maybe Int))
OdbcBindParam (OutParam (Maybe String))
OdbcBindParam (OutParam (Maybe UTCTime))
show/hide Instances
OdbcBindParam (InOutParam (Maybe Double))
OdbcBindParam (InOutParam (Maybe Int))
OdbcBindParam (InOutParam (Maybe String))
OdbcBindParam (InOutParam (Maybe UTCTime))
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 (Maybe Double)
OdbcBindParam (InOutParam (Maybe Int))
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))
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
buffer for column name +
-> SqlSmallIntsize of column name buffer +
-> Ptr SqlSmallIntsize of column name output string +
-> Ptr -> Ptr Buffer-> Ptr SqlULenoutput buffer +>col size (precision) hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5264 ->-> SqlLen-> Ptr SqlSmallIntoutput buffer size +>decimal digits (scale) hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5273 ->-> Ptr SqlLen-> Ptr SqlSmallIntoutput data size, or -1 (SQL_NULL_DATA) for null +>nullable: SQL_NO_NULLS, SQL_NULLABLE, or SQL_NULLABLE_UNKNOWN hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5282 ->-> IO -> IO :: StmtHandle:: StmtHdl-> Ptr -> Ptr -> Ptr -> Ptr -> IO -> IO :: StmtHandle -> IO :: StmtHdl -> IO sqlBindParametersqlGetData:: StmtHandle:: StmtHdlposition, 1-indexed +>column position, 1-indexed hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5420 ->-> SqlParamDirection-> SqlDataTypedirection: IN, OUT +>SQL data type: string, int, long, date, etc hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5429 ->-> SqlCDataType-> Ptr BufferC data type: char, int, long, float, etc +>output buffer hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5438 ->-> SqlDataType-> SqlLenSQL data type: string, int, long, date, etc +>output buffer size hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5447 ->-> SqlULen-> Ptr SqlLencol size (precision) +>output data size, or -1 (SQL_NULL_DATA) for null hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5456 ->-> -> IO SqlReturn
sqlCloseCursor :: StmtHdl -> IO SqlReturnsqlMoreResults :: StmtHdl -> IO SqlReturnsqlEndTran :: SqlSmallInt -> Handle -> -> IO SqlReturnsqlGetInfoTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. :: String -> String -> String -> :: String -> String -> String -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: String -> QueryString :: String -> QueryString :: String -> [ :: String -> [ :: Int -> String -> [ :: Int -> String -> [ :: String -> [ :: String -> [ = Ptr = Ptr TypeableTypeable String String String String (Maybe a) (Maybe a) PreparedStmtObj BindObj => PreparedStmtObj BindObj => (MaybeCalendarTime) (Maybe CalendarTime) (MaybeDouble) (Maybe Double) (MaybeInt) (Maybe Int) (MaybeString) (Maybe String) (MaybeUTCTime) (Maybe UTCTime) Show a => Show a => (Maybe a) (Maybe a) (MaybeDouble)) (Maybe Double)) (MaybeInt)) (Maybe Int)) (Maybe (Maybe (MaybeString)) (Maybe String)) (MaybeUTCTime)) (Maybe UTCTime)) Show a => Show a => (Maybe a)) (Maybe a)) (Maybe a)) (Maybe a)) PreparedStmtObj BindObj => PreparedStmtObj BindObj => :: String -> String -> String -> :: String -> String -> String -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: String -> QueryString :: String -> QueryString :: String -> [ :: String -> [ :: Int -> String -> [ :: Int -> String -> [ :: String -> [ :: String -> [ = Ptr = Ptr (MaybeDouble)) (Maybe Double)) (MaybeInt)) (Maybe Int)) (Maybe (Maybe (MaybeString)) (Maybe String)) (MaybeUTCTime)) (Maybe UTCTime)) Show a => Show a => (Maybe a)) (Maybe a)) (Maybe a)) (Maybe a)) PreparedStmtObj BindObj => PreparedStmtObj BindObj => Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CIntTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. = Ptr = Ptr = Ptr = Ptr = ForeignPtr = ForeignPtr = ForeignPtr = ForeignPtr = (ForeignPtrCShort, ForeignPtr = (ForeignPtr CShort, ForeignPtr , ForeignPtrCUShort), ForeignPtr CUShort) = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr , ForeignPtrCShort, ForeignPtrCUShort), ForeignPtr CShort, ForeignPtr CUShort)CIntString CInt String :: IO a -> ( :: IO a -> ( -> IO a) -> IO a -> IO a) -> IO a :: Int -> CInt :: Int -> CInt :: CInt -> CShort :: CInt -> CShort :: CInt -> CUShort :: CInt -> CUShort :: CStringLen -> CInt :: CStringLen -> CInt :: CStringLen -> CString :: CStringLen -> CString :: Ptr :: Ptr -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IOCInt -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IO CInt -> Ptr -> Ptr -> CInt -> CInt -> Ptr a -> IOCInt -> CInt -> CInt -> Ptr a -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> CString -> PtrCInt -> CString -> CInt -> CInt -> IOCInt -> CInt -> CString -> Ptr CInt -> CString -> CInt -> CInt -> IO CInt -> CInt -> -> CInt -> -> Ptr -> Ptr -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> -> CInt -> -> PtrCInt -> CInt -> -> Ptr CInt -> CInt -> -> IOCInt -> IO CInt -> CInt -> -> CInt -> -> CInt -> CInt -> -> CInt -> CInt -> -> IOCInt -> IO CInt -> Ptr -> Ptr -> CString -> CInt -> CString -> CInt -> CString -> CInt -> IOCInt -> CString -> CInt -> CString -> CInt -> CString -> CInt -> IO CInt -> IOCInt -> IO CInt -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CString -> CInt -> CInt -> IOCInt -> CString -> CInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt :: CInt -> IOCInt :: CInt -> IO CInt -> Word8 -> CInt -> IOCInt -> Word8 -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CString -> CInt -> CInt -> CInt -> IOCInt -> CString -> CInt -> CInt -> CInt -> IO CInt -> Ptr -> Ptr -> CInt -> -> CInt -> -> CInt -> CUShort -> PtrCShort -> PtrCUShort -> PtrCUShort -> CInt -> IOCInt -> CInt -> CUShort -> Ptr CShort -> Ptr CUShort -> Ptr CUShort -> CInt -> IO CInt -> CInt -> CInt -> -> CInt -> CInt -> -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> CShort -> CInt -> IOCInt -> CInt -> CShort -> CInt -> IO CInt -> Ptr -> Ptr -> CUInt -> -> CUInt -> -> CInt -> CUShort -> PtrCShort -> PtrCUShort -> PtrCUShort -> CUInt -> PtrCUInt -> CUInt -> IOCInt -> CInt -> CUShort -> Ptr CShort -> Ptr CUShort -> Ptr CUShort -> CUInt -> Ptr CUInt -> CUInt -> IO CInt -> FunPtr -> FunPtr -> FunPtr -> FunPtr -> IOCInt -> IO CInt -> CInt -> CInt -> Ptr -> CInt -> CInt -> Ptr -> CInt -> PtrWord8 -> PtrCShort -> IOCInt -> CInt -> Ptr Word8 -> Ptr CShort -> IO CInt -> CInt -> CInt -> Ptr -> CInt -> CInt -> Ptr -> PtrCInt -> PtrWord8 -> PtrCShort -> Ptr (PtrCShort) -> IOCInt -> Ptr CInt -> Ptr Word8 -> Ptr CShort -> Ptr (Ptr CShort) -> IO CInt -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> CInt -> PtrCInt -> CString -> CInt -> IO (CInt, String) -> CInt -> Ptr CInt -> CString -> CInt -> IO (CInt, String) -> CInt -> IO (CInt, String) -> CInt -> IO (CInt, String) :: CInt -> String :: CInt -> String :: CInt -> String -> String :: CInt -> String -> String :: CInt -> String -> :: CInt -> String -> -> CInt -> IO (Int, String) -> CInt -> IO (Int, String) -> CInt -> IO (Int, String) -> CInt -> IO (Int, String) -> IO (Int, String) -> IO (Int, String) -> IO (Int, String) -> IO (Int, String) :: CInt -> String -> a -> IO a :: CInt -> String -> a -> IO a :: Storable a => CInt -> String -> Ptr a -> IO a :: Storable a => CInt -> String -> Ptr a -> IO a :: IO :: IO :: CInt -> :: CInt -> -> IO -> IO :: CInt -> :: CInt -> -> IO () -> IO () -> CInt -> Ptr a -> CInt -> IO () -> CInt -> Ptr a -> CInt -> IO () -> CInt -> String -> CInt -> IO () -> CInt -> String -> CInt -> IO () :: Storable a => :: Storable a => -> CInt -> CInt -> IO a -> CInt -> CInt -> IO a -> Int -> IO -> Int -> IO :: String -> String -> String -> :: String -> String -> String -> -> IO -> IO -> IO () -> IO () :: IO () :: IO () -> IO () -> IO () -> String -> IO () -> String -> IO () -> IO -> IO -> CInt -> IO () -> CInt -> IO () -> IO () -> IO () -> CInt -> IO () -> CInt -> IO () -> IO () -> IO () -> IO () -> IO () -> String -> IO () -> String -> IO () -> Int -> IO () -> Int -> IO () -> Int -> Int -> CInt -> IO -> Int -> Int -> CInt -> IO :: String -> Int -> Bool -> String -> String :: String -> Int -> Bool -> String -> String -> Int -> CShort -> -> Int -> CShort -> -> Int -> CInt -> IO () -> Int -> CInt -> IO () -> Int -> -> Int -> -> Int -> CInt -> IO -> Int -> CInt -> IO -> IOCInt -> IO CInt :: ForeignPtrCShort -> Maybe a -> IO a -> IO (Maybe a) :: ForeignPtr CShort -> Maybe a -> IO a -> IO (Maybe a) :: CChar :: CChar :: CShort -> Int :: CShort -> Int :: CUShort -> Int :: CUShort -> Int :: CUChar -> Int :: CUChar -> Int :: PtrCUChar -> Int -> IOInt :: Ptr CUChar -> Int -> IO Int -> IO (MaybeString) -> IO (Maybe String) :: Int -> Int -> Int :: Int -> Int -> Int :: Int -> Word8 :: Int -> Word8 :: Int -> Word8 :: Int -> Word8 :: PtrWord8 -> IO () :: Ptr Word8 -> IO () :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeCalendarTime) -> IO (Maybe CalendarTime) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeUTCTime) -> IO (Maybe UTCTime) -> Int -> Word8 -> IO () -> Int -> Word8 -> IO () -> CalendarTime -> IO () -> CalendarTime -> IO () -> UTCTime -> IO () -> UTCTime -> IO () :: Storable a => :: Storable a => -> IO a -> IO a :: Storable a => ForeignPtrCShort -> :: Storable a => ForeignPtr CShort -> -> IO (Maybe a) -> IO (Maybe a) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeCInt) -> IO (Maybe CInt) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeInt) -> IO (Maybe Int) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeCDouble) -> IO (Maybe CDouble) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeDouble) -> IO (Maybe Double) -> IO -> IO = Ptr = Ptr = Ptr = Ptr = ForeignPtr = ForeignPtr = ForeignPtr = ForeignPtr = (ForeignPtrCShort, ForeignPtr = (ForeignPtr CShort, ForeignPtr , ForeignPtrCUShort), ForeignPtr CUShort) = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr = Ptr , ForeignPtrCShort, ForeignPtrCUShort), ForeignPtr CShort, ForeignPtr CUShort)CIntString CInt StringShowShow TypeableTypeable :: IO a -> ( :: IO a -> ( -> IO a) -> IO a -> IO a) -> IO a :: Int -> CInt :: Int -> CInt :: CInt -> CShort :: CInt -> CShort :: CInt -> CUShort :: CInt -> CUShort :: CStringLen -> CInt :: CStringLen -> CInt :: CStringLen -> CString :: CStringLen -> CString :: Ptr :: Ptr -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IOCInt -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IO CInt -> Ptr -> Ptr -> CInt -> CInt -> Ptr a -> IOCInt -> CInt -> CInt -> Ptr a -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> CString -> PtrCInt -> CString -> CInt -> CInt -> IOCInt -> CInt -> CString -> Ptr CInt -> CString -> CInt -> CInt -> IO CInt -> CInt -> -> CInt -> -> Ptr -> Ptr -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> -> CInt -> -> PtrCInt -> CInt -> -> Ptr CInt -> CInt -> -> IOCInt -> IO CInt -> CInt -> -> CInt -> -> CInt -> CInt -> -> CInt -> CInt -> -> IOCInt -> IO CInt -> Ptr -> Ptr -> CString -> CInt -> CString -> CInt -> CString -> CInt -> IOCInt -> CString -> CInt -> CString -> CInt -> CString -> CInt -> IO CInt -> IOCInt -> IO CInt -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CString -> CInt -> CInt -> IOCInt -> CString -> CInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt :: CInt -> IOCInt :: CInt -> IO CInt -> Word8 -> CInt -> IOCInt -> Word8 -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CString -> CInt -> CInt -> CInt -> IOCInt -> CString -> CInt -> CInt -> CInt -> IO CInt -> Ptr -> Ptr -> CInt -> -> CInt -> -> CInt -> CUShort -> PtrCShort -> PtrCUShort -> PtrCUShort -> CInt -> IOCInt -> CInt -> CUShort -> Ptr CShort -> Ptr CUShort -> Ptr CUShort -> CInt -> IO CInt -> CInt -> CInt -> -> CInt -> CInt -> -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> CShort -> CInt -> IOCInt -> CInt -> CShort -> CInt -> IO CInt -> Ptr -> Ptr -> CUInt -> -> CUInt -> -> CInt -> CUShort -> PtrCShort -> PtrCUShort -> PtrCUShort -> CUInt -> PtrCUInt -> CUInt -> IOCInt -> CInt -> CUShort -> Ptr CShort -> Ptr CUShort -> Ptr CUShort -> CUInt -> Ptr CUInt -> CUInt -> IO CInt -> FunPtr -> FunPtr -> FunPtr -> FunPtr -> IOCInt -> IO CInt -> CInt -> CInt -> Ptr -> CInt -> CInt -> Ptr -> CInt -> PtrWord8 -> PtrCShort -> IOCInt -> CInt -> Ptr Word8 -> Ptr CShort -> IO CInt -> CInt -> CInt -> Ptr -> CInt -> CInt -> Ptr -> PtrCInt -> PtrWord8 -> PtrCShort -> Ptr (PtrCShort) -> IOCInt -> Ptr CInt -> Ptr Word8 -> Ptr CShort -> Ptr (Ptr CShort) -> IO CInt -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> CInt -> PtrCInt -> CString -> CInt -> IO (CInt, String) -> CInt -> Ptr CInt -> CString -> CInt -> IO (CInt, String) -> CInt -> IO (CInt, String) -> CInt -> IO (CInt, String) :: CInt -> String :: CInt -> String :: CInt -> String -> String :: CInt -> String -> String :: CInt -> String -> :: CInt -> String -> -> CInt -> IO (Int, String) -> CInt -> IO (Int, String) -> CInt -> IO (Int, String) -> CInt -> IO (Int, String) -> IO (Int, String) -> IO (Int, String) -> IO (Int, String) -> IO (Int, String) :: CInt -> String -> a -> IO a :: CInt -> String -> a -> IO a :: Storable a => CInt -> String -> Ptr a -> IO a :: Storable a => CInt -> String -> Ptr a -> IO a :: IO :: IO :: CInt -> :: CInt -> -> IO -> IO :: CInt -> :: CInt -> -> IO () -> IO () -> CInt -> Ptr a -> CInt -> IO () -> CInt -> Ptr a -> CInt -> IO () -> CInt -> String -> CInt -> IO () -> CInt -> String -> CInt -> IO () :: Storable a => :: Storable a => -> CInt -> CInt -> IO a -> CInt -> CInt -> IO a -> Int -> IO -> Int -> IO :: String -> String -> String -> :: String -> String -> String -> -> IO -> IO -> IO () -> IO () :: IO () :: IO () -> IO () -> IO () -> String -> IO () -> String -> IO () -> IO -> IO -> CInt -> IO () -> CInt -> IO () -> IO () -> IO () -> CInt -> IO () -> CInt -> IO () -> IO () -> IO () -> IO () -> IO () -> String -> IO () -> String -> IO () -> Int -> IO () -> Int -> IO ()-> Int-> Int-> Int-> Int-> CInt-> CInt-> IO-> IO :: String -> Int -> Bool -> String -> String :: String -> Int -> Bool -> String -> String-> Int-> Int-> CShort-> CShort-> Int-> Int-> CInt-> CInt-> IO ()-> IO ()-> Int-> Int-> Int-> Int-> CInt-> CInt-> IO-> IO -> IOCInt -> IO CInt :: ForeignPtrCShort -> Maybe a -> IO a -> IO (Maybe a) :: ForeignPtr CShort -> Maybe a -> IO a -> IO (Maybe a) :: CChar :: CChar :: CShort -> Int :: CShort -> Int :: CUShort -> Int :: CUShort -> Int :: CUChar -> Int :: CUChar -> Int :: PtrCUChar -> Int -> IOInt :: Ptr CUChar -> Int -> IO Int -> IO (MaybeString) -> IO (Maybe String) :: Int -> Int -> Int :: Int -> Int -> Int :: Int -> Word8 :: Int -> Word8 :: Int -> Word8 :: Int -> Word8 :: PtrWord8 -> IO () :: Ptr Word8 -> IO () :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeCalendarTime) -> IO (Maybe CalendarTime) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeUTCTime) -> IO (Maybe UTCTime) -> Int -> Word8 -> IO () -> Int -> Word8 -> IO () -> CalendarTime -> IO () -> CalendarTime -> IO () -> UTCTime -> IO () -> UTCTime -> IO () :: Storable a => :: Storable a => -> IO a -> IO a :: Storable a => ForeignPtrCShort -> :: Storable a => ForeignPtr CShort -> -> IO (Maybe a) -> IO (Maybe a) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeCInt) -> IO (Maybe CInt) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeInt) -> IO (Maybe Int) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeCDouble) -> IO (Maybe CDouble) :: ForeignPtrCShort -> :: ForeignPtr CShort -> -> IO (MaybeDouble) -> IO (Maybe Double) -> IO -> IO Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.] -> ] -> String StringString StringString StringString StringString StringString StringInt IntString StringString StringString String :: String -> QueryString -> [ :: String -> QueryString -> [] -> ] -> :: Int -> String -> QueryString -> [ :: Int -> String -> QueryString -> [] -> ] -> :: String -> QueryString -> [ :: String -> QueryString -> [] -> ] -> :: Int -> String -> QueryString -> [ :: Int -> String -> QueryString -> [] -> ] -> :: String -> QueryString -> [ :: String -> QueryString -> [] -> ] -> :: String -> QueryString :: String -> QueryString :: String -> [ :: String -> [ :: Int -> String -> [ :: Int -> String -> [ :: String -> [ :: String -> [TypeableTypeable String String String String (Maybe a) (Maybe a) PreparedStmtObj BindObj => PreparedStmtObj BindObj => String) String) (MaybeDouble) (Maybe Double) (MaybeFloat) (Maybe Float) (MaybeInt) (Maybe Int) (MaybeInt64) (Maybe Int64) (MaybeString) (Maybe String) (MaybeUTCTime) (Maybe UTCTime) Show a => Show a => (Maybe a) (Maybe a) ] -> ] -> String StringString StringString StringString StringString StringString StringInt IntString StringString StringString String :: String -> QueryString -> [ :: String -> QueryString -> [] -> ] -> :: Int -> String -> QueryString -> [ :: Int -> String -> QueryString -> [] -> ] -> :: String -> QueryString -> [ :: String -> QueryString -> [] -> ] -> :: Int -> String -> QueryString -> [ :: Int -> String -> QueryString -> [] -> ] -> :: String -> QueryString -> [ :: String -> QueryString -> [] -> ] -> :: String -> QueryString :: String -> QueryString :: String -> [ :: String -> [ :: Int -> String -> [ :: Int -> String -> [ :: String -> [ :: String -> [Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. = Ptr = Ptr = Ptr = Ptr = CUInt = CUInt = CInt = CInt = CInt = CIntIntString Int String :: IO a -> ( :: IO a -> ( -> IO a) -> IO a -> IO a) -> IO a :: Integral a => a -> String -> any :: Integral a => a -> String -> any :: CStringLen -> CString :: CStringLen -> CString :: CStringLen -> CInt :: CStringLen -> CInt :: CString -> IO :: CString -> IO -> IO () -> IO () -> IO () -> IO () -> CString -> CString = CInt = CInt -> IO -> IO -> IOCString -> IO CString -> CString -> IOCString -> CString -> IO CString = Ptr () -> = Ptr () -> -> IO () -> IO () = Ptr () -> CString -> IO () = Ptr () -> CString -> IO () -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> FunPtr -> FunPtr -> Ptr () -> IO (FunPtr -> Ptr () -> IO (FunPtr -> FunPtr -> FunPtr -> Ptr () -> IO (FunPtr -> Ptr () -> IO (FunPtr -> CString -> CInt -> Ptr -> CString -> CInt -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> CInt -> IO -> CInt -> IO -> CString -> CString -> CInt -> Ptr -> CString -> CString -> CInt -> Ptr -> IO -> IO -> CString -> CInt -> Ptr -> CString -> CInt -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> CInt -> IO -> CInt -> IO -> IO -> IO = CInt = CInt -> IOCString -> IO CString -> IO () -> IO () -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> CInt -> IOCString -> CInt -> IO CString -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IO -> CInt -> IO -> CInt -> CInt -> IO (PtrWord8) -> CInt -> CInt -> IO (Ptr Word8) -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> IOCString -> IO CString -> IOCString -> IO CString -> IO -> IO -> PtrWord8 -> CInt -> IOCInt -> Ptr Word8 -> CInt -> IO CInt -> CString -> IOCInt -> CString -> IO CInt -> IO -> IO = CInt = CInt -> IO -> IO = CInt = CInt = CInt = CInt -> IO -> IO -> CString -> IO -> CString -> IO -> CString -> IOCInt -> CString -> IO CInt -> IOCInt -> IO CInt -> CInt -> PtrWord8 -> CUInt -> IOCInt -> CInt -> Ptr Word8 -> CUInt -> IO CInt -> CInt -> PtrWord8 -> CUInt -> IOCInt -> CInt -> Ptr Word8 -> CUInt -> IO CInt -> CInt -> CInt -> -> CInt -> CInt -> -> IOCInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> IOCInt -> IO CInt -> IOString -> IO String :: String -> IO :: String -> IO -> IO () -> IO () :: a -> IO (PtrWord8) :: a -> IO (Ptr Word8) :: PtrWord8 -> IO a :: Ptr Word8 -> IO a :: a -> Int :: a -> Int :: CInt :: CInt :: (IO (PtrWord8)) :: (IO (Ptr Word8)) :: Char -> CChar :: Char -> CChar :: CChar -> Char :: CChar -> Char :: Int -> CInt :: Int -> CInt -> IO -> IO -> String -> String -> [ -> String -> String -> [] -> IOString] -> IO String -> String -> IO (String, String, -> String -> IO (String, String, -> String -> [ -> String -> [] -> IO (String, String, ] -> IO (String, String, -> String -> [ -> String -> [] -> IO (String, String, ] -> IO (String, String, -> String -> [ -> String -> [] -> IO (] -> IO (, Int), Int) -> String -> IO ( -> String -> IO (, Int), Int) -> String -> IO ( -> String -> IO (, Int), Int) -> String -> IO ( -> String -> IO (, Int), Int) -> String -> [ -> String -> [] -> IO (] -> IO (, Int), Int) -> String -> [ -> String -> [] -> CInt -> IO (] -> CInt -> IO (, Int), Int) -> String -> String -> [ -> String -> String -> [] -> IO (] -> IO (, Int), Int) -> IO () -> IO () -> Int -> Int -> IO (PtrWord8) -> Int -> Int -> IO (Ptr Word8) -> Int -> Int -> IO a -> Int -> Int -> IO a -> Int -> Int -> IOString -> Int -> Int -> IO String -> Int -> Int -> IOInt -> Int -> Int -> IO Int -> Int -> Int -> IOInt64 -> Int -> Int -> IO Int64 -> Int -> Int -> IODouble -> Int -> Int -> IO Double -> Int -> Int -> IOFloat -> Int -> Int -> IO Float -> Int -> Int -> IOUTCTime -> Int -> Int -> IO UTCTime -> Int -> Int -> IOCalendarTime -> Int -> Int -> IO CalendarTime -> Int -> Int -> IOBool -> Int -> Int -> IO Bool :: String -> Int -> Bool -> String -> String :: String -> Int -> Bool -> String -> String :: Int :: Int -> String -> Handle -> IO () -> String -> Handle -> IO () = Ptr = Ptr = Ptr = Ptr = CUInt = CUInt = CInt = CInt = CInt = CIntIntString Int StringShowShow TypeableTypeable :: IO a -> ( :: IO a -> ( -> IO a) -> IO a -> IO a) -> IO a :: Integral a => a -> String -> any :: Integral a => a -> String -> any :: CStringLen -> CString :: CStringLen -> CString :: CStringLen -> CInt :: CStringLen -> CInt :: CString -> IO :: CString -> IO -> IO () -> IO () -> IO () -> IO () -> CString -> CString = CInt = CInt -> IO -> IO -> IOCString -> IO CString -> CString -> IOCString -> CString -> IO CString = Ptr () -> = Ptr () -> -> IO () -> IO () = Ptr () -> CString -> IO () = Ptr () -> CString -> IO () -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> IO (FunPtr -> FunPtr -> FunPtr -> Ptr () -> IO (FunPtr -> Ptr () -> IO (FunPtr -> FunPtr -> FunPtr -> Ptr () -> IO (FunPtr -> Ptr () -> IO (FunPtr -> CString -> CInt -> Ptr -> CString -> CInt -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> CInt -> IO -> CInt -> IO -> CString -> CString -> CInt -> Ptr -> CString -> CString -> CInt -> Ptr -> IO -> IO -> CString -> CInt -> Ptr -> CString -> CInt -> Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> CInt -> IO -> CInt -> IO -> IO -> IO = CInt = CInt -> IOCString -> IO CString -> IO () -> IO () -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> CInt -> IOCString -> CInt -> IO CString -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IO -> CInt -> IO -> CInt -> CInt -> IO (PtrWord8) -> CInt -> CInt -> IO (Ptr Word8) -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> IOCString -> IO CString -> IOCString -> IO CString -> IO -> IO -> PtrWord8 -> CInt -> IOCInt -> Ptr Word8 -> CInt -> IO CInt -> CString -> IOCInt -> CString -> IO CInt -> IO -> IO = CInt = CInt -> IO -> IO = CInt = CInt = CInt = CInt -> IO -> IO -> CString -> IO -> CString -> IO -> CString -> IOCInt -> CString -> IO CInt -> IOCInt -> IO CInt -> CInt -> PtrWord8 -> CUInt -> IOCInt -> CInt -> Ptr Word8 -> CUInt -> IO CInt -> CInt -> PtrWord8 -> CUInt -> IOCInt -> CInt -> Ptr Word8 -> CUInt -> IO CInt -> CInt -> CInt -> -> CInt -> CInt -> -> IOCInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> IOCInt -> IO CInt -> IOString -> IO String :: String -> IO :: String -> IO -> IO () -> IO () :: a -> IO (PtrWord8) :: a -> IO (Ptr Word8) :: PtrWord8 -> IO a :: Ptr Word8 -> IO a :: a -> Int :: a -> IntCalendarTime CalendarTimeChar CharDouble DoubleFloat FloatInt IntInt16 Int16Int32 Int32Int64 Int64Integer IntegerString StringUTCTime UTCTime (Maybe a) (Maybe a) :: CInt :: CInt :: (IO (PtrWord8)) :: (IO (Ptr Word8)) :: Char -> CChar :: Char -> CChar :: CChar -> Char :: CChar -> Char :: Int -> CInt :: Int -> CInt -> IO -> IO -> String -> String -> [ -> String -> String -> [] -> IOString] -> IO String -> String -> IO (String, String, -> String -> IO (String, String, -> String -> [ -> String -> [] -> IO (String, String, ] -> IO (String, String, -> String -> [ -> String -> [] -> IO (String, String, ] -> IO (String, String, -> String -> [ -> String -> [] -> IO (] -> IO (, Int), Int) -> String -> IO ( -> String -> IO (, Int), Int) -> String -> IO ( -> String -> IO (, Int), Int) -> String -> IO ( -> String -> IO (, Int), Int) -> String -> [ -> String -> [] -> IO (] -> IO (, Int), Int) -> String -> [ -> String -> [] -> CInt -> IO (] -> CInt -> IO (, Int), Int) -> String -> String -> [ -> String -> String -> [] -> IO (] -> IO (, Int), Int) -> IO () -> IO () -> Int -> Int -> IO (PtrWord8) -> Int -> Int -> IO (Ptr Word8) -> Int -> Int -> IO a -> Int -> Int -> IO a -> Int -> Int -> IOString -> Int -> Int -> IO String -> Int -> Int -> IOInt -> Int -> Int -> IO Int -> Int -> Int -> IOInt64 -> Int -> Int -> IO Int64 -> Int -> Int -> IODouble -> Int -> Int -> IO Double -> Int -> Int -> IOFloat -> Int -> Int -> IO Float -> Int -> Int -> IOUTCTime -> Int -> Int -> IO UTCTime -> Int -> Int -> IOCalendarTime -> Int -> Int -> IO CalendarTime -> Int -> Int -> IOBool -> Int -> Int -> IO Bool :: String -> Int -> Bool -> String -> String :: String -> Int -> Bool -> String -> String :: Int :: Int -> String -> Handle -> IO () -> String -> Handle -> IO ()Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.TypeableTypeable String String Int64 Int64 String String (Maybe a) (Maybe a) PreparedStmtObj BindObj => PreparedStmtObj BindObj => (MaybeCalendarTime) (Maybe CalendarTime) (MaybeDouble) (Maybe Double) (MaybeInt) (Maybe Int) (MaybeInt64) (Maybe Int64) (MaybeString) (Maybe String) (MaybeUTCTime) (Maybe UTCTime) Show a => Show a => (Maybe a) (Maybe a) :: String -> :: String -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: Int -> QueryString -> :: Int -> QueryString -> :: QueryString -> :: QueryString -> :: String -> QueryString :: String -> QueryString :: String -> [ :: String -> [ :: Int -> String -> [ :: Int -> String -> [ :: String -> [ :: String -> [ Int64 Int64Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. = Ptr = Ptr = Ptr = Ptr = PtrWord8 = Ptr Word8 a = FunPtr (Ptr a -> CInt -> PtrCString -> PtrCString -> IOInt) a = FunPtr (Ptr a -> CInt -> Ptr CString -> Ptr CString -> IO Int) = FunPtr (PtrWord8 -> IO ()) = FunPtr (Ptr Word8 -> IO ())IntString Int String :: IO a -> ( :: IO a -> ( -> IO a) -> IO a -> IO a) -> IO a :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CStringLen -> CString :: CStringLen -> CString :: CStringLen -> CInt :: CStringLen -> CInt = CString = CString = CString = CString -> Ptr -> Ptr -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> CInt -> Ptr -> CInt -> Ptr -> PtrCString -> IOCInt -> Ptr CString -> IO CInt a -> Ptr a -> PtrCString -> IOCInt a -> Ptr a -> Ptr CString -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCLLong -> IO CLLong :: Ptr a -> IO () :: Ptr a -> IO () -> IOCInt -> IO CInt -> IO -> IO -> CInt -> IOInt -> CInt -> IO Int -> CInt -> IO -> CInt -> IO -> CInt -> IOCDouble -> CInt -> IO CDouble -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IOCLLong -> CInt -> IO CLLong -> CInt -> IO -> CInt -> IO -> CInt -> IO -> CInt -> IO -> CInt -> -> CInt -> -> CInt -> -> CInt -> -> IOCInt -> IO CInt -> CInt -> CDouble -> IOCInt -> CInt -> CDouble -> IO CInt -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> CInt -> CLLong -> IOCInt -> CInt -> CLLong -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> -> CInt -> -> CInt -> -> CInt -> -> IOCInt -> IO CInt -> CInt -> -> CInt -> -> CInt -> -> CInt -> -> IOCInt -> IO CInt -> IO -> IO :: Int -> :: Int -> -> IO a -> IO a -> CInt -> IO a -> IO a -> CInt -> IO a -> IO a -> CInt -> a -> IO a -> CInt -> a -> IO a :: Storable a => :: Storable a => -> CInt -> Ptr a -> IO a -> CInt -> Ptr a -> IO a :: String -> IO :: String -> IO -> IO () -> IO () -> String -> IOInt -> String -> IO Int -> IOInt -> IO Int -> String -> IO -> String -> IO -> IOCInt -> IO CInt -> IO () -> IO () -> IO () -> IO () -> Int -> IO () -> Int -> IO () -> Int -> IOInt -> Int -> IO Int -> Int -> IOInt64 -> Int -> IO Int64 -> Int -> IODouble -> Int -> IO Double -> Int -> IO (MaybeString) -> Int -> IO (Maybe String) -> Int -> IO (ForeignPtr -> Int -> IO (ForeignPtr -> Int -> Double -> IO () -> Int -> Double -> IO () -> Int -> Int -> IO () -> Int -> Int -> IO () -> Int -> Int64 -> IO () -> Int -> Int64 -> IO () -> Int -> IO () -> Int -> IO () -> Int -> String -> IO () -> Int -> String -> IO () -> Int -> -> Int -> -> Int -> IO () -> Int -> IO () = Ptr = Ptr = Ptr = Ptr = PtrWord8 = Ptr Word8 a = FunPtr (Ptr a -> CInt -> PtrCString -> PtrCString -> IOInt) a = FunPtr (Ptr a -> CInt -> Ptr CString -> Ptr CString -> IO Int) = FunPtr (PtrWord8 -> IO ()) = FunPtr (Ptr Word8 -> IO ())IntString Int StringShowShow TypeableTypeable :: IO a -> ( :: IO a -> ( -> IO a) -> IO a -> IO a) -> IO a :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CInt :: CStringLen -> CString :: CStringLen -> CString :: CStringLen -> CInt :: CStringLen -> CInt = CString = CString = CString = CString -> Ptr -> Ptr -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> CInt -> Ptr -> CInt -> Ptr -> PtrCString -> IOCInt -> Ptr CString -> IO CInt a -> Ptr a -> PtrCString -> IOCInt a -> Ptr a -> Ptr CString -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCInt -> IO CInt -> IOCLLong -> IO CLLong :: Ptr a -> IO () :: Ptr a -> IO () -> IOCInt -> IO CInt -> IO -> IO -> CInt -> IOInt -> CInt -> IO Int -> CInt -> IO -> CInt -> IO -> CInt -> IOCDouble -> CInt -> IO CDouble -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> IOCLLong -> CInt -> IO CLLong -> CInt -> IO -> CInt -> IO -> CInt -> IO -> CInt -> IO -> CInt -> -> CInt -> -> CInt -> -> CInt -> -> IOCInt -> IO CInt -> CInt -> CDouble -> IOCInt -> CInt -> CDouble -> IO CInt -> CInt -> CInt -> IOCInt -> CInt -> CInt -> IO CInt -> CInt -> CLLong -> IOCInt -> CInt -> CLLong -> IO CInt -> CInt -> IOCInt -> CInt -> IO CInt -> CInt -> -> CInt -> -> CInt -> -> CInt -> -> IOCInt -> IO CInt -> CInt -> -> CInt -> -> CInt -> -> CInt -> -> IOCInt -> IO CInt -> IO -> IO :: Int -> :: Int -> -> IO a -> IO a -> CInt -> IO a -> IO a -> CInt -> IO a -> IO a -> CInt -> a -> IO a -> CInt -> a -> IO a :: Storable a => :: Storable a => -> CInt -> Ptr a -> IO a -> CInt -> Ptr a -> IO a :: String -> IO :: String -> IO -> IO () -> IO () -> String -> IOInt -> String -> IO Int -> IOInt -> IO Int -> String -> IO -> String -> IO -> IOCInt -> IO CInt -> IO () -> IO () -> IO () -> IO () -> Int -> IO () -> Int -> IO () -> Int -> IOInt -> Int -> IO Int -> Int -> IOInt64 -> Int -> IO Int64 -> Int -> IODouble -> Int -> IO Double -> Int -> IO (MaybeString) -> Int -> IO (Maybe String) -> Int -> IO (ForeignPtr -> Int -> IO (ForeignPtr -> Int -> Double -> IO () -> Int -> Double -> IO () -> Int -> Int -> IO () -> Int -> Int -> IO () -> Int -> Int64 -> IO () -> Int -> Int64 -> IO () -> Int -> IO () -> Int -> IO () -> Int -> String -> IO () -> Int -> String -> IO () -> Int -> -> Int -> -> Int -> IO () -> Int -> IO ()Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. :: String :: String -> -> :: String -> QueryString :: String -> QueryString :: Int -> String -> QueryStringTuned :: Int -> String -> QueryStringTuned :: Int :: Int :: String :: String -> -> :: String -> QueryString :: String -> QueryString :: Int -> String -> QueryStringTuned :: Int -> String -> QueryStringTuned :: Int :: IntTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Show a => Show a => :: a -> String :: a -> String :: (MonadIO m, :: (MonadIO m, :: (Integral a, Real b) => a -> a -> a -> a -> a -> b -> UTCTime :: (Integral a, Real b) => a -> a -> a -> a -> a -> b -> UTCTime :: Integral a => a -> a -> a -> a -> a -> a -> CalendarTime :: Integral a => a -> a -> a -> a -> a -> a -> CalendarTime :: Int64 -> (Int64, Int64, Int64, Int64, Int64, Int64) :: Int64 -> (Int64, Int64, Int64, Int64, Int64, Int64) :: (Integral a1, Integral a2, Integral a3, Integral a4, Integral a5, Integral a6) => (a1, a2, a3, a4, a5, a6) -> Int64 :: (Integral a1, Integral a2, Integral a3, Integral a4, Integral a5, Integral a6) => (a1, a2, a3, a4, a5, a6) -> Int64 :: CalendarTime -> Int64 :: CalendarTime -> Int64 :: Int64 -> CalendarTime :: Int64 -> CalendarTime :: Int64 -> UTCTime :: Int64 -> UTCTime :: (Char -> Bool) -> String -> [String] :: (Char -> Bool) -> String -> [String] :: (Char -> Bool) -> String -> [String] :: (Char -> Bool) -> String -> [String] :: Eq a => [a] -> [a] -> [Int] :: Eq a => [a] -> [a] -> [Int] :: String -> UTCTime :: String -> UTCTime :: String -> CalendarTime :: String -> CalendarTime :: String -> (Int, Int, Int, Int, Int, Double, Int) :: String -> (Int, Int, Int, Int, Int, Double, Int) :: (Integral a, Integral b) => UTCTime -> String -> (a -> a) -> (b -> String) -> String :: (Integral a, Integral b) => UTCTime -> String -> (a -> a) -> (b -> String) -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: CalendarTime -> String :: CalendarTime -> StringShow a => Show a => :: a -> String :: a -> StringString StringShow a => Show a => :: (MonadIO m, :: (MonadIO m, :: (Integral a, Real b) => a -> a -> a -> a -> a -> b -> UTCTime :: (Integral a, Real b) => a -> a -> a -> a -> a -> b -> UTCTime :: Integral a => a -> a -> a -> a -> a -> a -> CalendarTime :: Integral a => a -> a -> a -> a -> a -> a -> CalendarTime :: Int64 -> (Int64, Int64, Int64, Int64, Int64, Int64) :: Int64 -> (Int64, Int64, Int64, Int64, Int64, Int64) :: (Integral a1, Integral a2, Integral a3, Integral a4, Integral a5, Integral a6) => (a1, a2, a3, a4, a5, a6) -> Int64 :: (Integral a1, Integral a2, Integral a3, Integral a4, Integral a5, Integral a6) => (a1, a2, a3, a4, a5, a6) -> Int64 :: CalendarTime -> Int64 :: CalendarTime -> Int64 :: Int64 -> CalendarTime :: Int64 -> CalendarTime :: Int64 -> UTCTime :: Int64 -> UTCTime :: (Char -> Bool) -> String -> [String] :: (Char -> Bool) -> String -> [String] :: (Char -> Bool) -> String -> [String] :: (Char -> Bool) -> String -> [String] :: Eq a => [a] -> [a] -> [Int] :: Eq a => [a] -> [a] -> [Int] :: String -> UTCTime :: String -> UTCTime :: String -> CalendarTime :: String -> CalendarTime :: String -> (Int, Int, Int, Int, Int, Double, Int) :: String -> (Int, Int, Int, Int, Int, Double, Int) :: (Integral a, Integral b) => UTCTime -> String -> (a -> a) -> (b -> String) -> String :: (Integral a, Integral b) => UTCTime -> String -> (a -> a) -> (b -> String) -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: UTCTime -> String :: CalendarTime -> String :: CalendarTime -> StringTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. :: CString -> IOString :: CString -> IO String :: CStringLen -> IOString :: CStringLen -> IO String :: String -> IOCString :: String -> IO CString :: String -> (CString -> IO a) -> IO a :: String -> (CString -> IO a) -> IO a :: String -> (CStringLen -> IO a) -> IO a :: String -> (CStringLen -> IO a) -> IO a :: String -> String :: String -> String :: String -> String :: String -> String :: String -> Int :: String -> Int :: [Word8] -> String :: [Word8] -> String :: String -> [Word8] :: String -> [Word8] :: CString -> IOString :: CString -> IO String :: CStringLen -> IOString :: CStringLen -> IO String :: String -> IOCString :: String -> IO CString :: String -> (CString -> IO a) -> IO a :: String -> (CString -> IO a) -> IO a :: String -> (CStringLen -> IO a) -> IO a :: String -> (CStringLen -> IO a) -> IO a :: String -> String :: String -> String :: String -> String :: String -> String :: String -> Int :: String -> Int :: [Word8] -> String :: [Word8] -> String :: String -> [Word8] :: String -> [Word8]Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumerator, Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.Enumerator2 (Type/Class)2 (Data Constructor)Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.InternalEnumerator, Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumerator, Database.InternalEnumerator, Database.InternalEnumerator, Database.InternalEnumerator, Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumerator, destroyQueryTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.fetchColfreeHandleTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.getInfoDatabaseNameTakusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumerator, Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.ODBC.Enumerator4 (Data Constructor)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumerator, Database.InternalEnumerator, Database.InternalEnumerator, Database.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorTakusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumerator, Database.InternalEnumerator, SqlInfoTypeDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.EnumeratorDatabase.InternalEnumeratorDatabase.Enumerator, Database.ODBC.Enumerator, Database.Oracle.Enumerator, Database.PostgreSQL.Enumerator, Database.Sqlite.Enumerator2 (Type/Class)2 (Data Constructor)3 (Type/Class)4 (Type/Class)sqlDescribeColTakusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Database.InternalEnumerator, Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. (Index)Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Takusen is a DBMS access library. Like HSQL, we support +>Takusen is a DBMS access library. Like HSQL and HDBC, we support hunk ./doc/html/index.html 126 ->
:: ConnHdldecimal digits (scale) +>
-> SqlInfoTypeinformation type hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5551 ->-> Ptr -> Ptr input+output buffer +>output buffer hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5560 ->-> SqlLen-> SqlSmallIntbuffer size +>output buffer size hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5569 ->-> Ptr SqlLen-> Ptr SqlSmallIntinput+output data size, or -1 (SQL_NULL_DATA) for null +>output data size, or -1 (SQL_NULL_DATA) for null hunk ./doc/html/Database-ODBC-OdbcFunctions.html 5578 ->-> IO -> IO sqlMoreResults :: StmtHandle -> IO SqlReturnsqlNativeSql
:: ConnHdlsqlEndTran :: SqlSmallInt -> Handle -> SqlSmallInt -> IO -> MyCStringsql text in +
-> SqlIntegersize of sql text +
-> MyCStringbuffer for output text +
-> SqlIntegersize of output buffer +
-> Ptr SqlIntegersize of text in output buffer +
-> IO
allocBufferFor
1 (Type/Class)
2 (Data Constructor)
1 (Function)2 (Function)
bindRun
3 (Type/Class)ConnHdl
1 (Type/Class)
2 (Data Constructor)
3 (Function)connDbms
connHdl
destroyStmt
1 (Function)
2 (Function)
executeCommand
fetchOneRow
freeBuffer
freeHelper
getInfoDbmsName
getInfoDbmsVer
getInfoDriverName
getInfoDriverVer
getInfoString
getNativeSql
1 (Function)
2 (Function)
makeQuery
2 (Data Constructor)
3 (Type/Class)
1 (Type/Class)
2 (Data Constructor)
PreparedStmt
1 (Type/Class)2 (Data Constructor)PreparedStmt
3 (Function)
Database.InternalEnumerator
3 (Type/Class)StmtHdl
sqlGetInfo
sqlNativeSql
sqlNumResultCols
stmtDbms
stmtHdl
throwIfDBNull
Database.InternalEnumerator