[Initial rebuild of Haddock docs. alistair@abayley.org**20060707140236] { adddir ./doc adddir ./doc/html addfile ./doc/html/Control-Exception-MonadIO.html hunk ./doc/html/Control-Exception-MonadIO.html 1 + + +Control.Exception.MonadIO
 ContentsIndex
Control.Exception.MonadIO
Documentation
class MonadIO m => CaughtMonadIO m where
Methods
gcatch :: m a -> (Exception -> m a) -> m a
gcatchJust :: (Exception -> Maybe b) -> m a -> (b -> m a) -> m a
show/hide Instances
gtry :: CaughtMonadIO m => m b -> m (Either Exception b)
gtryJust :: CaughtMonadIO m => (Exception -> Maybe b) -> m b1 -> m (Either b b1)
gbracket :: CaughtMonadIO m => m t -> (t -> m a) -> (t -> m b) -> m b
gfinally :: CaughtMonadIO m => m t -> m a -> m t
Produced by Haddock version 0.7
addfile ./doc/html/Database-Enumerator.html hunk ./doc/html/Database-Enumerator.html 1 + + +Database.Enumerator
 ContentsIndex
Database.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Contents
Usage +
Iteratee Functions +
result and result' +
Bind Parameters +
Multiple (and nested) Result Sets +
Sessions and Transactions +
Exceptions and handlers +
Preparing and Binding +
Iteratees and Cursors +
Utilities +
Description

Abstract database interface, providing a left-fold enumerator + and cursor operations. +

There is a stub: Database.Stub.Enumerator. + This lets you run the test cases without having a working DBMS installation. +

Additional reading: +

Note that there are a few functions that are exported from each backend + implementation which *are* exposed to the API user, and which are useful, + but are not (necessarily) in this module. They include: +

  • connect (obviously DBMS specific) +
  • prepareStmt, sql, prefetch +
Synopsis
data DBM mark sess a
withSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark . DBM mark sess a) -> IO a
commit :: ISession s => DBM mark s ()
rollback :: ISession s => DBM mark s ()
beginTransaction :: (MonadReader s (ReaderT s IO), ISession s) => IsolationLevel -> DBM mark s ()
withTransaction :: ISession s => IsolationLevel -> DBM mark s a -> DBM mark s a
data IsolationLevel
= ReadUncommitted
| ReadCommitted
| RepeatableRead
| Serialisable
| Serializable
execDDL :: Command stmt s => stmt -> DBM mark s ()
execDML :: Command stmt s => stmt -> DBM mark s Int
data DBException
= DBError SqlState Int String
| DBFatal SqlState Int String
| DBUnexpectedNull RowNum ColNum
| DBNoData
basicDBExceptionReporter :: CaughtMonadIO m => DBException -> m ()
reportRethrow :: CaughtMonadIO m => DBException -> m ()
formatDBException :: DBException -> String
catchDB :: CaughtMonadIO m => m a -> (DBException -> m a) -> m a
catchDBError :: CaughtMonadIO m => Int -> m a -> (DBException -> m a) -> m a
ignoreDBError :: CaughtMonadIO m => Int -> m a -> m a
throwDB :: DBException -> a
newtype PreparedStmt mark stmt = PreparedStmt stmt
withPreparedStatement :: (Typeable a, IPrepared stmt sess bstmt bo) => PreparationA sess stmt -> (PreparedStmt mark stmt -> DBM mark sess a) -> DBM mark sess a
withBoundStatement :: (Typeable a, IPrepared stmt s bstmt bo) => PreparedStmt mark stmt -> [BindA s stmt bo] -> (bstmt -> DBM mark s a) -> DBM mark s a
bindP :: DBBind a sess stmt bo => a -> BindA sess stmt bo
doQuery :: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) => stmt -> i -> seed -> DBM mark sess seed
type IterResult seedType = Either seedType seedType
type IterAct m seedType = seedType -> m (IterResult seedType)
currentRowNum :: IQuery q sess b => q -> IO Int
data NextResultSet mark stmt = NextResultSet (PreparedStmt mark stmt)
data RefCursor a = RefCursor a
cursorIsEOF :: DBCursor mark (DBM mark s) a -> DBM mark s Bool
cursorCurrent :: DBCursor mark (DBM mark s) a -> DBM mark s a
cursorNext :: DBCursor mark (DBM mark s) a -> DBM mark s (DBCursor mark (DBM mark s) a)
withCursor :: (Typeable a, Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) => stmt -> i -> seed -> (DBCursor mark (DBM mark sess) seed -> DBM mark sess a) -> DBM mark sess a
ifNull :: Maybe a -> a -> a
result :: Monad m => IterAct m a
result' :: Monad m => IterAct m a
print_ :: (MonadIO m, MyShow a) => a -> m ()
Usage +

Let's look at some example code: +

 -- sample code, doesn't necessarily compile
+ module MyDbExample is
+
+ import Database.Oracle.Enumerator
+ import Database.Enumerator
+ ...
+
+ query1Iteratee :: (Monad m) => Int -> String -> Double -> IterAct m [(Int, String, Double)]
+ query1Iteratee a b c accum = result' ((a, b, c):accum)
+
+ -- non-query actions.
+ otherActions session = do
+   execDDL "create table blah"
+   execDML "insert into blah ..."
+   commit
+   -- Use withTransaction to delimit a transaction.
+   -- It will commit at the end, or rollback if an error occurs.
+   withTransaction Serialisable $ do
+     execDML "update blah ..."
+     execDML "insert into blah ..."
+
+ main :: IO ()
+ main = do
+   withSession (connect "user" "password" "server") $ do
+     -- simple query, returning reversed list of rows.
+     r <- doQuery (sql "select a, b, c from x") query1Iteratee []
+     putStrLn $ show r
+     otherActions session
+

Notes: +

  • connection is made by withSession, + which also disconnects when done i.e. withSession + delimits the connection. + You must pass it a connection action, which is back-end specific, + and created by calling the connect + function from the relevant back-end. +
  • inside the session, the usual transaction delimiter commands are usable + e.g. beginTransaction [isolation-level], + commit, rollback, and + withTransaction. + We also provide execDML and execDDL. +
  • non-DML and -DDL commands - i.e. queries - are processed by + doQuery (this is the API for our left-fold). + See more explanation and examples below in Iteratee Functions and + Bind Parameters sections. +

The first argument to doQuery must be an instance of + Statement. + Each back-end will provide a useful set of Statement instances + and associated constructor functions for them. + For example, the Sqlite and Oracle back-ends have: +

  • for basic, all-text statements (no bind variables): +
 sql "select ..."
+
  • for a select with bind variables and row caching: +
 prefetch 100 "select ..." [bindP ..., bindP ...]
+
  • for a reusable prepared statement: we have to first create the + prepared statement, and then bind in a separate step. + This separation lets us re-use prepared statements: +
 let stmt = prepareStmt (sql "select ...")
+ withPreparedStatement stmt $ \pstmt ->
+   withBoundStatement pstmt [bindP ..., bindP ...] $ \bstmt -> do
+     result <- doQuery bstmt iter seed
+     ...
+

The PostgreSQL backend additionally requires that when preparing statements, + you (1) give a name to the prepared statement, + and (2) specify types for the bind parameters. + The list of bind-types is created by applying the bindType functions + to dummy values of the appropriate types. +

 let stmt = prepareStmt "stmtname" (sql "select ...") [bindType "", bindType (0::Int)]
+ withPreparedStatement stmt $ \pstmt -> ...
+

A longer explanation of bind variables is in the Bind Parametes section below. +

Iteratee Functions +

doQuery takes an iteratee function, of n arguments. + Argument n is the accumulator (or seed). + For each row that is returned by the query, + the iteratee function is called with the data from that row in + arguments 1 to n-1, and the current accumulated value in the argument n. +

The iteratee function returns the next value of the accumulator, + wrapped in an Either. + If the Either value is Left, then the query will terminate, + with the new value of the accumulator/seed returned. + If the value is Right, then the query will continue, with the next row + begin fed to the iteratee function, along with the new accumulator/seed. +

In the example above, query1Iteratee simply conses the new row (as a tuple) + to the front of the accumulator. + The initial seed passed to doQuery was an empty list. + Consing the rows to the front of the list results in a list that is the result set + with the rows in reverse order. +

The types of values that can be used as arguments to the iteratee function + are back-end specific; they must be instances of the class + DBType. + Most backends directly support the usual lowest-common-denominator set + supported by most DBMS's: Int, String, + Double, CalendarTime. + By directly support we mean there is type-specific marshalling code + implemented. + Int64 is often, but not always, supported. +

Indirect support for Read- and Show-able types + is supported by marshalling to and from Strings. + This is done automatically by the back-end; + there is no need for user-code to perform the marshalling, + as long as instances of Read and Show are defined. +

The iteratee function operates in the DBM monad, + so if you want to do IO in it you must use liftIO + (e.g. liftIO $ putStrLn "boo" ) to lift the IO action into DBM. +

The iteratee function is not restricted to just constructing lists. + For example, a simple counter function would ignore its arguments, + and the accumulator would simply be the count e.g. +

 counterIteratee :: (Monad m) => Int -> IterAct m Int
+ counterIteratee _ i = result' $ (1 + i)
+

The iteratee function that you pass to doQuery + needs type information, + at least for the arguments if not the return type (which is typically + determined by the type of the seed). + The type synonyms IterAct and IterResult give some convenience + in writing type signatures for iteratee functions. +

 type IterResult seedType = Either seedType seedType
+ type IterAct m seedType = seedType -> m (IterResult seedType)
+

Without them, the type for counterIteratee would be: +

 counterIteratee :: (Monad m) => Int -> Int -> m (Either Int Int)
+

which doesn't seem so onerous, but for more elaborate seed types + (think large tuples) it certainly helps e.g. +

 iter :: Monad m =>
+      String -> Double -> CalendarTime -> [(String, Double, CalendarTime)]
+   -> m (Either [(String, Double, CalendarTime)] [(String, Double, CalendarTime)] )
+

becomes: +

 iter :: Monad m =>
+      String -> Double -> CalendarTime -> IterAct m [(String, Double, CalendarTime)]
+
result and result' +

The result (lazy) and result (strict) functions are another convenient shorthand + for returning values from iteratee functions. The return type from an interatee is actually + Either seed seed, where you return Right if you want processing to continue, + or Left if you want processing to stop before the result-set is exhausted. + The common case is: +

 query1Iteratee a b c accum = return (Right ((a, b, c):accum))
+

which we can write as +

 query1Iteratee a b c accum = result $ (a, b, c):accum)
+

We have lazy and strict versions of result. The strict version is almost certainly + the one you want to use. If you come across a case where the lazy function is useful, + please tell us about it. The lazy function tends to exhaust the stack for large result-sets, + whereas the strict function does not. + This is due to the accumulation of a large number of unevaluated thunks, + and will happen even for simple arithmetic operations such as counting or summing. +

If you use the lazy function and you have stack/memory problems, do some profiling. + With GHC: +

  • ensure the iteratee has its own cost-centre (make it a top-level function) +
  • compile with -prof -auto-all +
  • run with +RTS -p -hr -RTS +
  • run hp2ps over the resulting .hp file to get a .ps document, and take a look at it. + Retainer sets are listed on the RHS, and are prefixed with numbers e.g. (13)CAF, (2)SYSTEM. + At the bottom of the .prof file you'll find the full descriptions of the retainer sets. + Match the number in parentheses on the .ps graph with a SET in the .prof file; + the one at the top of the .ps graph is the one using the most memory. +

You'll probably find that the lazy iteratee is consuming all of the stack with lazy thunks, + which is why we recommend the strict function. +

Bind Parameters +

Support for bind variables varies between backends. +

We call withPreparedStatement function to prepare + the statement, and then call withBoundStatement + to provide the bind values and execute the query. + The value returned by withBoundStatement + is an instance of the Statement class, so it can be passed to + doQuery for result-set processing. +

When we call withPreparedStatement, we must pass + it a "preparation action", which is simply an action that returns + the prepared query. The function to create this action varies between + backends, and by convention is called prepareStmt (although it may + also have differently-named variations; see + preparePrefetch, for example. +

With PostgreSQL, we must specify the type of the bind parameters + when the query is prepared, so the prepareStmt + function takes a list of bindType values. + Also, PostgreSQL requires that prepared statements are named, + although you can use "" as the name. +

With Sqlite and Oracle, we simply pass the query text to prepareStmt, + so things are slightly simpler for these backends. +

Perhaps an example will explain it better: +

 postgresBindExample = do
+   let
+     query = sql "select blah from blahblah where id = ? and code = ?"
+     iter :: (Monad m) => String -> IterAct m [String]
+     iter s acc = result $ s:acc
+     bindVals = [bindP (12345::Int), bindP "CODE123"]
+     bindTypes = [bindType (0::Int), bindType ""]
+   withPreparedStatement (prepareStmt "stmt1" query bindTypes) $ \pstmt -> do
+     withBoundStatement pstmt bindVals $ \bstmt -> do
+       actual <- doQuery query iter []
+       liftIO (print actual)
+

There is also a statement preparation function + preparePrefetch which takes + an extra parameter: the number of rows to prefetch + (from each call to the server). +

The Oracle/Sqlite example code is almost the same, except for the + call to prepareStmt: +

 sqliteBindExample = do
+   let
+     query = sql "select blah from blahblah where id = ? and code = ?"
+     iter :: (Monad m) => String -> IterAct m [String]
+     iter s acc = result $ s:acc
+     bindVals = [bindP (12345::Int), bindP "CODE123"]
+   withPreparedStatement (prepareStmt query) $ \pstmt -> do
+     withBoundStatement pstmt bindVals $ \bstmt -> do
+       actual <- doQuery query iter []
+       liftIO (print actual)
+

It can be a bit tedious to always use the withPreparedStatement+withBoundStatement + combination, so for the case where you don't plan to re-use the query, + we support a short-cut for bundling the query text and parameters. + The next example is valid for PostgreSQL, Sqlite, and Oracle; + for Sqlite we provide a dummy prefetch + function to ensure we have a consistent API. + Sqlite has no facility for prefetching - it's an embedded database, so no + network round-trip - so Sqlite the back-end ignores the prefetch count: +

 bindShortcutExample = do
+   let
+     iter :: (Monad m) => String -> IterAct m [String]
+     iter s acc = result $ s:acc
+     bindVals = [bindP (12345::Int), bindP "CODE123"]
+     query = prefetch 1000 "select blah from blahblah where id = ? and code = ?" bindVals
+   actual <- doQuery query iter []
+   liftIO (print actual)
+

A caveat of using prefetch with PostgreSQL is that you must be inside a transaction. + This is because the PostgreSQL implementation uses a cursor and "FETCH FORWARD" + to implement fetching blocks of rows in network calls, + and PostgreSQL requires that cursors are only used inside transactions. + It can be as simple as wrapping calls to doQuery by + withTransaction, + or you may prefer to delimit your transactions elsewhere (the API supports + beginTransaction and + commit, if you prefer to use them): +

   withTransaction RepeatableRead $ do
+     actual <- doQuery query iter []
+     liftIO (print actual)
+

For Int and Double bind values, + we have to tell the compiler about the types. + I assume this is due to interaction (which I don't fully understand and therefore + cannot explain in any detail) with the numeric literal defaulting mechanism. + Note that for non-numeric literals the compiler can determine the correct + types to use. +

If you omit type information for numeric literals, from GHC the error + message looks something like this: +

 Database/PostgreSQL/Test/Enumerator.lhs:194:4:
+     Overlapping instances for Database.InternalEnumerator.DBBind a
+                                  Session
+                                  Database.PostgreSQL.PGEnumerator.PreparedStmt
+                                  Database.PostgreSQL.PGEnumerator.BindObj
+       arising from use of `bindP' at Database/PostgreSQL/Test/Enumerator.lhs:194:4-8
+     Matching instances:
+       Imported from Database.PostgreSQL.PGEnumerator:
+     instance (Database.InternalEnumerator.DBBind (Maybe a)
+                              Session
+                              Database.PostgreSQL.PGEnumerator.PreparedStmt
+                              Database.PostgreSQL.PGEnumerator.BindObj) =>
+          Database.InternalEnumerator.DBBind a
+                             Session
+                             Database.PostgreSQL.PGEnumerator.PreparedStmt
+                             Database.PostgreSQL.PGEnumerator.BindObj
+       Imported from Database.PostgreSQL.PGEnumerator:
+     instance Database.InternalEnumerator.DBBind (Maybe Double)
+                        ....
+
Multiple (and nested) Result Sets +

Initial support for returning multiple result sets from a single + statement exists in PostgreSQL, and will be added to Oracle and + other backends (except Sqlite, where such functionality does not exist) +

The general idea is to invoke a database procedure or function which + returns cursor variables. The variables can be processed by + doQuery in one of two styles: linear or nested. +

Linear style: +

Here we assume the existence of the following PostgreSQL function + (this function is used in the test suite in Database.PostgreSQL.Test.Enumerator.): +

 CREATE OR REPLACE FUNCTION takusenTestFunc() RETURNS SETOF refcursor AS $$
+ DECLARE refc1 refcursor; refc2 refcursor;
+ BEGIN
+     OPEN refc1 FOR SELECT n*n from t_natural where n < 10 order by 1;
+     RETURN NEXT refc1;
+     OPEN refc2 FOR SELECT n, n*n, n*n*n from t_natural where n < 10 order by 1;
+     RETURN NEXT refc2;
+ END;$$ LANGUAGE plpgsql;
+

... then this code shows how linear processing of cursors would be done: +

   withTransaction RepeatableRead $ do
+   withPreparedStatement (prepareStmt "stmt1" (sql "select * from takusenTestFunc()") []) $ \pstmt -> do
+   withBoundStatement pstmt [] $ \bstmt -> do
+     dummy <- doQuery bstmt iterMain []
+     result1 <- doQuery (NextResultSet pstmt) iterRS1 []
+     result2 <- doQuery (NextResultSet pstmt) iterRS2 []
+   where
+     iterMain :: (Monad m) => (RefCursor String) -> IterAct m [RefCursor String]
+     iterMain c acc = result (acc ++ [c])
+     iterRS1 :: (Monad m) => Int -> IterAct m [Int]
+     iterRS1 i acc = result (acc ++ [i])
+     iterRS2 :: (Monad m) => Int -> Int -> Int -> IterAct m [(Int, Int, Int)]
+     iterRS2 i i2 i3 acc = result (acc ++ [(i, i2, i3)])
+

Notes: +

  • the results of the first iteratee are discarded (this is not required, + but in this case all the only column is a RefCursor, + and its values are already saved elsewhere). +
  • the use of a RefCursor String + type in the iteratee function indicates + to the backend that it should save each cursor value returned, + which it does by stuffing them into a list attached to the + prepared statement object. +
  • saved cursors are consumed one-at-a-time by calling doQuery, + passing NextResultSet pstmt. + This simply pulls the next cursor of the list + - they're processed in the order they were pushed on (FIFO) - + and processes it with the given iteratee. +
  • if you try to process too many cursors i.e. make too many calls + to doQuery passing NextResultSet pstmt, + then an exception will be thrown. + OTOH, failing to process returned cursors will not raise errors, + but the cursors will remain open on the server until either the transaction + or session ends. +

Nested style: +

The linear style of cursor processing is the only style supported by + MS SQL Server and ODBC. However, PostgreSQL and Oracle also support + using nested cursors in queries. +

Assuming we have these functions in the database: +

 CREATE OR REPLACE FUNCTION takusenTestFunc(lim int4) RETURNS refcursor AS $$
+ DECLARE refc refcursor;
+ BEGIN
+     OPEN refc FOR SELECT n, takusenTestFunc2(n) from t_natural where n < lim order by n;
+     RETURN refc;
+ END; $$ LANGUAGE plpgsql;
+
 CREATE OR REPLACE FUNCTION takusenTestFunc2(lim int4) RETURNS refcursor AS $$
+ DECLARE refc refcursor;
+ BEGIN
+     OPEN refc FOR SELECT n from t_natural where n < lim order by n;
+     RETURN refc;
+ END; $$ LANGUAGE plpgsql;
+

... then this code shows how nested queries mights work in PostgreSQL: +

 selectNestedMultiResultSet = do
+   let
+     q = "SELECT n, takusenTestFunc(n) from t_natural where n < 10 order by n"
+     iterMain   (i::Int) (c::RefCursor String) acc = result' ((i,c):acc)
+     iterInner  (i::Int) (c::RefCursor String) acc = result' ((i,c):acc)
+     iterInner2 (i::Int) acc = result' (i:acc)
+   withTransaction RepeatableRead $ do
+     rs <- doQuery (sql q) iterMain []
+     flip mapM_ rs $ \(outer, c) -> do
+       rs <- doQuery c iterInner []
+       flip mapM_ rs $ \(inner, c) -> do
+         rs <- doQuery c iterInner2 []
+         flip mapM_ rs $ \i -> do
+           liftIO (putStrLn (show outer ++ " " ++ show inner ++ " " ++ show i))
+

Just to make it clear: the outer query returns a result-set that includes + a RefCursor column. Each cursor from that column is passed to + doQuery to process it's result-set; + here we use mapM_ to apply an IO action to the list returned by + doQuery. +

Sessions and Transactions +
data DBM mark sess a
show/hide Instances
CaughtMonadIO (DBM mark si)
(ISession sess, ??? a sess) => Monad (DBM mark sess a)
(ISession sess, ??? a sess) => MonadIO (DBM mark sess a)
withSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark . DBM mark sess a) -> IO a
Typeable constraint is to prevent the leakage of Session and other + marked objects. +
commit :: ISession s => DBM mark s ()
rollback :: ISession s => DBM mark s ()
beginTransaction :: (MonadReader s (ReaderT s IO), ISession s) => IsolationLevel -> DBM mark s ()
withTransaction :: ISession s => IsolationLevel -> DBM mark s a -> DBM mark s a
Perform an action as a transaction: commit afterwards, + unless there was an exception, in which case rollback. +
data IsolationLevel
Constructors
ReadUncommitted
ReadCommitted
RepeatableRead
Serialisable
Serializablefor alternative spellers +
show/hide Instances
execDDL :: Command stmt s => stmt -> DBM mark s ()
execDML :: Command stmt s => stmt -> DBM mark s Int
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
basicDBExceptionReporter :: CaughtMonadIO m => DBException -> m ()
This simple handler reports the error to stdout and swallows it + i.e. it doesn't propagate. +
reportRethrow :: CaughtMonadIO m => DBException -> m ()
This handler reports the error and propagates it + (usually to force the program to halt). +
formatDBException :: DBException -> String
catchDB :: CaughtMonadIO m => m a -> (DBException -> m a) -> m a
Catch DBExceptions thrown in the DBM + monad. +
catchDBError :: CaughtMonadIO m => Int -> m a -> (DBException -> m a) -> m a
If you want to trap a specific error number, use this. + It passes anything else up. +
ignoreDBError :: CaughtMonadIO m => Int -> m a -> m a
Analogous to catchDBError, but ignores specific errors instead + (propagates anything else). +
throwDB :: DBException -> a
Throw a DBException. It's just a type-specific throwDyn. +
Preparing and Binding +
newtype PreparedStmt mark stmt
Constructors
PreparedStmt stmt
withPreparedStatement
:: (Typeable a, IPrepared stmt sess bstmt bo)
=> PreparationA sess stmtpreparation action to create prepared statement; + this action is usually created by prepareStmt +
-> (PreparedStmt mark stmt -> DBM mark sess a)DBM action that takes a prepared statement +
-> DBM mark sess a

Prepare a statement and run a DBM action over it. + This gives us the ability to re-use a statement, + for example by passing different bind values for each execution. +

The Typeable constraint is to prevent the leakage of marked things. + The type of bound statements should not be exported (and should not be + in Typeable) so the bound statement can't leak either. +

withBoundStatement
:: (Typeable a, IPrepared stmt s bstmt bo)
=> PreparedStmt mark stmtprepared statement created by withPreparedStatement +
-> [BindA s stmt bo]bind values +
-> (bstmt -> DBM mark s a)action to run over bound statement +
-> DBM mark s a

Applies a prepared statement to bind variables to get a bound statement, + which is passed to the provided action. + Note that by the time it is passed to the action, the query or command + has usually been executed. + A bound statement would normally be an instance of + Statement, so it can be passed to + doQuery + in order to process the result-set, and also an instance of + Command, so that we can write + re-usable DML statements (inserts, updates, deletes). +

The Typeable constraint is to prevent the leakage of marked things. + The type of bound statements should not be exported (and should not be + in Typeable) so the bound statement can't leak either. +

bindP :: DBBind a sess stmt bo => a -> BindA sess stmt bo
Iteratees and Cursors +
doQuery
:: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b)
=> stmtquery +
-> iiteratee function +
-> seedseed value +
-> DBM mark sess seed
The left-fold interface. +
type IterResult seedType = Either seedType seedType
IterResult and IterAct give us some type sugar. + Without them, the types of iteratee functions become + quite unwieldy. +
type IterAct m seedType = seedType -> m (IterResult seedType)
currentRowNum :: IQuery q sess b => q -> IO Int
data NextResultSet mark stmt
Constructors
NextResultSet (PreparedStmt mark stmt)
show/hide Instances
Statement (NextResultSet mark PreparedStmt) Session Query
Statement (NextResultSet mark PreparedStmt) Session Query
data RefCursor a
Constructors
RefCursor a
show/hide Instances
cursorIsEOF :: DBCursor mark (DBM mark s) a -> DBM mark s Bool

cursorIsEOF's return value tells you if there are any more rows or not. + If you call cursorNext when there are no more rows, + a DBNoData exception is thrown. + Cursors are automatically closed and freed when: +

  • the iteratee returns Left a +
  • the query result-set is exhausted. +

To make life easier, we've created a withCursor function, + which will clean up if an error (exception) occurs, + or the code exits early. + You can nest them to get interleaving, if you desire: +

  withCursor query1 iter1 [] $ \c1 -> do
+    withCursor query2 iter2 [] $ \c2 -> do
+      r1 <- cursorCurrent c1
+      r2 <- cursorCurrent c2
+      ...
+      return something
+
cursorCurrent :: DBCursor mark (DBM mark s) a -> DBM mark s a
Returns the results fetched so far, processed by iteratee function. +
cursorNext :: DBCursor mark (DBM mark s) a -> DBM mark s (DBCursor mark (DBM mark s) a)
Advance the cursor. Returns the cursor. The return value is usually ignored. +
withCursor
:: (Typeable a, Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b)
=> stmtquery +
-> iiteratee function +
-> seedseed value +
-> (DBCursor mark (DBM mark sess) seed -> DBM mark sess a)action taking cursor parameter +
-> DBM mark sess a
Ensures cursor resource is properly tidied up in exceptional cases. + Propagates exceptions after closing cursor. + The Typeable constraint is to prevent cursors and other marked values + (like cursor computations) from escaping. +
Utilities +
ifNull
:: Maybe anullable value +
-> avalue to substitute if first parameter is null +
-> a
Useful utility function, for SQL weenies. +
result :: Monad m => IterAct m a
Another useful utility function. + Use this to return a value from an iteratee function (the one passed to + doQuery). + Note that you should probably nearly always use the strict version. +
result' :: Monad m => IterAct m a
A strict version. This is recommended unless you have a specific need for laziness, + as the lazy version will gobble stack and heap. + If you have a large result-set (in the order of 10-100K rows or more), + it is likely to exhaust the standard 1M GHC stack. + Whether or not result eats memory depends on what x does: + if it's a delayed computation then it almost certainly will. + This includes consing elements onto a list, + and arithmetic operations (counting, summing, etc). +
print_ :: (MonadIO m, MyShow a) => a -> m ()
Like print, except that Strings are not escaped or quoted. +
Produced by Haddock version 0.7
addfile ./doc/html/Database-InternalEnumerator.html hunk ./doc/html/Database-InternalEnumerator.html 1 + + +Database.InternalEnumerator
 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
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. +

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)
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 PreparedStmt Session Query
Statement PreparedStmt 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 (RefCursor StmtHandle) Session Query
Statement (RefCursor String) Session Query
Statement (NextResultSet mark PreparedStmt) Session Query
Statement (NextResultSet mark PreparedStmt) 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
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 PreparedStmt Session BoundStmt BindObj
IPrepared PreparedStmt Session BoundStmt BindObj
IPrepared PreparedStmt 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
show/hide Instances
DBBind (Maybe a) Session PreparedStmt BindObj => DBBind a Session PreparedStmt BindObj
DBBind (Maybe a) Session PreparedStmt BindObj => DBBind a Session PreparedStmt BindObj
DBBind (Maybe a) Session PreparedStmt BindObj => DBBind a Session PreparedStmt BindObj
DBBind (Maybe CalendarTime) Session PreparedStmt BindObj
DBBind (Maybe CalendarTime) Session PreparedStmt BindObj
DBBind (Maybe Double) Session PreparedStmt BindObj
DBBind (Maybe Double) Session PreparedStmt BindObj
DBBind (Maybe Double) Session PreparedStmt BindObj
DBBind (Maybe Float) Session PreparedStmt BindObj
DBBind (Maybe Int) Session PreparedStmt BindObj
DBBind (Maybe Int) Session PreparedStmt BindObj
DBBind (Maybe Int) Session PreparedStmt BindObj
DBBind (Maybe Int64) Session PreparedStmt BindObj
DBBind (Maybe Int64) Session PreparedStmt BindObj
DBBind (Maybe String) Session PreparedStmt BindObj
DBBind (Maybe String) Session PreparedStmt BindObj
DBBind (Maybe String) Session PreparedStmt BindObj
Show a => DBBind (Maybe a) Session PreparedStmt BindObj
Show a => DBBind (Maybe a) Session PreparedStmt BindObj
Show a => DBBind (Maybe a) Session PreparedStmt BindObj
DBBind (Out (Maybe Int)) Session PreparedStmt 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
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 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 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 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
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
DBType (RefCursor StmtHandle) Query ColumnBuffer
DBType (RefCursor String) Query ColumnBuffer
throwIfDBNull :: Monad m => m (RowNum, ColNum) -> m (Maybe a) -> m a
Used by instances of DBType to throw an exception + when a null (Nothing) is returned. + Will work for any type, as you pass the fetch action in the fetcher arg. +
Exceptions and handlers +
data DBException
Constructors
DBError SqlState Int StringDBMS error message. +
DBFatal SqlState Int String
DBUnexpectedNull RowNum ColNumthe iteratee function used for queries accepts both nullable (Maybe) and + non-nullable types. If the query itself returns a null in a column where a + non-nullable type was specified, we can't handle it, so DBUnexpectedNull is thrown. +
DBNoDataThrown by cursor functions if you try to fetch after the end. +
show/hide Instances
throwDB :: DBException -> a
Throw a DBException. It's just a type-specific throwDyn. +
type ColNum = Int
type RowNum = Int
type SqlState = (SqlStateClass, SqlStateSubClass)
type SqlStateClass = String
type SqlStateSubClass = String
Produced by Haddock version 0.7
addfile ./doc/html/Database-Oracle-Enumerator.html hunk ./doc/html/Database-Oracle-Enumerator.html 1 + + +Database.Oracle.Enumerator
 ContentsIndex
Database.Oracle.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Oracle OCI implementation of Database.Enumerator. +
Documentation
data Session
show/hide Instances
ISession Session
Command BoundStmt Session
Command QueryString Session
Command String Session
IQuery Query Session ColumnBuffer
Statement BoundStmt Session Query
Statement PreparedStmt Session Query
Statement QueryString Session Query
Statement QueryStringTuned Session Query
Statement StmtBind Session Query
Statement String Session Query
DBBind (Maybe a) Session PreparedStmt BindObj => DBBind a Session PreparedStmt BindObj
IPrepared PreparedStmt Session BoundStmt BindObj
Statement (RefCursor StmtHandle) Session Query
DBBind (Maybe CalendarTime) Session PreparedStmt BindObj
DBBind (Maybe Double) Session PreparedStmt BindObj
DBBind (Maybe Int) Session PreparedStmt BindObj
DBBind (Maybe String) Session PreparedStmt BindObj
Show a => DBBind (Maybe a) Session PreparedStmt BindObj
DBBind (Out (Maybe Int)) Session PreparedStmt BindObj
Statement (NextResultSet mark PreparedStmt) Session Query
connect :: String -> String -> String -> ConnectA Session
prepareStmt :: QueryString -> PreparationA Session PreparedStmt
sql :: String -> QueryString
sqlbind :: String -> [BindA Session PreparedStmt BindObj] -> QueryStringTuned
prefetch :: Int -> String -> [BindA Session PreparedStmt BindObj] -> QueryStringTuned
module Database.Enumerator
Produced by Haddock version 0.7
addfile ./doc/html/Database-Oracle-OCIConstants.html hunk ./doc/html/Database-Oracle-OCIConstants.html 1 + + +Database.Oracle.OCIConstants
 ContentsIndex
Database.Oracle.OCIConstants
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Contents
Used all over the place: +
Handle types: +
Error code types: +
Attribute types: +
Authentication options: +
Syntax types (i.e. does the DBMS understand v7 or v8 syntax, etc): +
Scrollable Cursor Options: +
OCI datatypes: +
Transaction types; parameters for ociTransStart. +
Description
Contains CInt equivalents of the #defines in the oci library headers. + This is not a complete set; just enough to get the Haskell libraries working. + This also might not be particularly portable, but I don't think Oracle are going + to change these in a hurry (that would break compiled programs, wouldn't it?). +
Synopsis
oci_DEFAULT :: CInt
oci_CRED_RDBMS :: CInt
oci_CRED_EXT :: CInt
oci_CRED_PROXY :: CInt
oci_NTV_SYNTAX :: CInt
oci_FETCH_NEXT :: CInt
oci_FETCH_FIRST :: CInt
oci_FETCH_LAST :: CInt
oci_FETCH_PRIOR :: CInt
oci_FETCH_ABSOLUTE :: CInt
oci_FETCH_RELATIVE :: CInt
oci_FETCH_RESERVED :: CInt
oci_SQLT_CHR :: CInt
oci_SQLT_NUM :: CInt
oci_SQLT_INT :: CInt
oci_SQLT_FLT :: CInt
oci_SQLT_STR :: CInt
oci_SQLT_VNU :: CInt
oci_SQLT_LNG :: CInt
oci_SQLT_VCS :: CInt
oci_SQLT_RID :: CInt
oci_SQLT_DAT :: CInt
oci_SQLT_VBI :: CInt
oci_SQLT_BIN :: CInt
oci_SQLT_LBI :: CInt
oci_SQLT_UIN :: CInt
oci_SQLT_LVC :: CInt
oci_SQLT_LVB :: CInt
oci_SQLT_AFC :: CInt
oci_SQLT_AVC :: CInt
oci_SQLT_RSET :: CInt
oci_TRANS_READONLY :: CInt
oci_TRANS_READWRITE :: CInt
oci_TRANS_SERIALIZABLE :: CInt
Used all over the place: +
oci_DEFAULT :: CInt
Handle types: +
Error code types: +
Attribute types: +
Authentication options: +
oci_CRED_RDBMS :: CInt
Found in $ORAHOME/oci/include/oci.h +
oci_CRED_EXT :: CInt
oci_CRED_PROXY :: CInt
Syntax types (i.e. does the DBMS understand v7 or v8 syntax, etc): +
oci_NTV_SYNTAX :: CInt
Found in $ORAHOME/oci/include/oci.h +
Scrollable Cursor Options: +
oci_FETCH_NEXT :: CInt
Found in $ORAHOME/oci/include/oci.h +
oci_FETCH_FIRST :: CInt
oci_FETCH_LAST :: CInt
oci_FETCH_PRIOR :: CInt
oci_FETCH_ABSOLUTE :: CInt
oci_FETCH_RELATIVE :: CInt
oci_FETCH_RESERVED :: CInt
OCI datatypes: +
oci_SQLT_CHR :: CInt
Found in $ORAHOME/oci/include/ocidfn.h +
oci_SQLT_NUM :: CInt
oci_SQLT_INT :: CInt
oci_SQLT_FLT :: CInt
oci_SQLT_STR :: CInt
oci_SQLT_VNU :: CInt
oci_SQLT_LNG :: CInt
oci_SQLT_VCS :: CInt
oci_SQLT_RID :: CInt
oci_SQLT_DAT :: CInt
oci_SQLT_VBI :: CInt
oci_SQLT_BIN :: CInt
oci_SQLT_LBI :: CInt
oci_SQLT_UIN :: CInt
oci_SQLT_LVC :: CInt
oci_SQLT_LVB :: CInt
oci_SQLT_AFC :: CInt
oci_SQLT_AVC :: CInt
oci_SQLT_RSET :: CInt
Transaction types; parameters for ociTransStart. +
oci_TRANS_READONLY :: CInt
Found in $ORAHOME/oci/include/oci.h. + There are more than this, but they're related to complicated + transaction-management stuff in the OCI libraries that I don't understand. + These should be sufficient to support the simple transaction model + understood by most developers. +
oci_TRANS_READWRITE :: CInt
oci_TRANS_SERIALIZABLE :: CInt
Produced by Haddock version 0.7
addfile ./doc/html/Database-Oracle-OCIFunctions.html hunk ./doc/html/Database-Oracle-OCIFunctions.html 1 + + +Database.Oracle.OCIFunctions
 ContentsIndex
Database.Oracle.OCIFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Contents
Foreign OCI functions +
OCI error reporting +
Allocating Handles (i.e. creating OCI data structures, and memory management) +
Connecting and detaching +
Transactions +
Issuing queries +
Description

Simple wrappers for OCI functions (FFI). +

The functions in this file are simple wrappers for OCI functions. + The wrappers add error detection and exceptions; + functions in this module raise OCIException. + The next layer up traps these and turns them into DBException. +

Note that OCIException does not contain the error number and text + returned by getOCIErrorMsg. + It is the job of the next layer (module) up to catch the OCIException + and then call getOCIErrorMsg to get the actual error details. + The OCIException simply contains the error number returned by + the OCI call, and some text identifying the wrapper function. + See formatErrorCodeDesc for the set of possible values for the OCI error numbers. +

Synopsis
data OCIStruct = OCIStruct
type OCIHandle = Ptr OCIStruct
data OCIBuffer = OCIBuffer
type BufferPtr = Ptr OCIBuffer
type ColumnResultBuffer = ForeignPtr OCIBuffer
data Context = Context
type ContextPtr = Ptr Context
data EnvStruct = EnvStruct
type EnvHandle = Ptr EnvStruct
data ErrorStruct = ErrorStruct
type ErrorHandle = Ptr ErrorStruct
data ServerStruct = ServerStruct
type ServerHandle = Ptr ServerStruct
data UserStruct = UserStruct
type UserHandle = Ptr UserStruct
data ConnStruct = ConnStruct
type ConnHandle = Ptr ConnStruct
data SessStruct = SessStruct
type SessHandle = Ptr SessStruct
data StmtStruct = StmtStruct
type StmtHandle = Ptr StmtStruct
data DefnStruct = DefnStruct
type DefnHandle = Ptr DefnStruct
data ParamStruct = ParamStruct
type ParamHandle = Ptr ParamStruct
data BindStruct = BindStruct
type BindHandle = Ptr BindStruct
type ColumnInfo = (DefnHandle, ColumnResultBuffer, ForeignPtr CShort, ForeignPtr CShort)
data OCIException = OCIException CInt String
catchOCI :: IO a -> (OCIException -> IO a) -> IO a
throwOCI :: OCIException -> a
mkCInt :: Int -> CInt
mkCShort :: CInt -> CShort
cStrLen :: CStringLen -> CInt
cStr :: CStringLen -> CString
ociEnvCreate :: Ptr EnvHandle -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IO CInt
ociHandleAlloc :: OCIHandle -> Ptr OCIHandle -> CInt -> CInt -> Ptr a -> IO CInt
ociHandleFree :: OCIHandle -> CInt -> IO CInt
ociErrorGet :: OCIHandle -> CInt -> CString -> Ptr CInt -> CString -> CInt -> CInt -> IO CInt
ociParamGet :: OCIHandle -> CInt -> ErrorHandle -> Ptr OCIHandle -> CInt -> IO CInt
ociAttrGet :: OCIHandle -> CInt -> BufferPtr -> Ptr CInt -> CInt -> ErrorHandle -> IO CInt
ociAttrSet :: OCIHandle -> CInt -> BufferPtr -> CInt -> CInt -> ErrorHandle -> IO CInt
ociLogon :: EnvHandle -> ErrorHandle -> Ptr ConnHandle -> CString -> CInt -> CString -> CInt -> CString -> CInt -> IO CInt
ociLogoff :: ConnHandle -> ErrorHandle -> IO CInt
ociSessionBegin :: ConnHandle -> ErrorHandle -> SessHandle -> CInt -> CInt -> IO CInt
ociSessionEnd :: ConnHandle -> ErrorHandle -> SessHandle -> CInt -> IO CInt
ociServerAttach :: ServerHandle -> ErrorHandle -> CString -> CInt -> CInt -> IO CInt
ociServerDetach :: ServerHandle -> ErrorHandle -> CInt -> IO CInt
ociTerminate :: CInt -> IO CInt
ociTransStart :: ConnHandle -> ErrorHandle -> Word8 -> CInt -> IO CInt
ociTransCommit :: ConnHandle -> ErrorHandle -> CInt -> IO CInt
ociTransRollback :: ConnHandle -> ErrorHandle -> CInt -> IO CInt
ociStmtPrepare :: StmtHandle -> ErrorHandle -> CString -> CInt -> CInt -> CInt -> IO CInt
ociDefineByPos :: StmtHandle -> Ptr DefnHandle -> ErrorHandle -> CInt -> BufferPtr -> CInt -> CShort -> Ptr CShort -> Ptr CShort -> Ptr CShort -> CInt -> IO CInt
ociStmtExecute :: ConnHandle -> StmtHandle -> ErrorHandle -> CInt -> CInt -> OCIHandle -> OCIHandle -> CInt -> IO CInt
ociStmtFetch :: StmtHandle -> ErrorHandle -> CInt -> CShort -> CInt -> IO CInt
ociBindByPos :: StmtHandle -> Ptr BindHandle -> ErrorHandle -> CUInt -> BufferPtr -> CInt -> CUShort -> Ptr CShort -> Ptr CUShort -> Ptr CUShort -> Ptr CUInt -> Ptr CUInt -> CUInt -> IO CInt
ociBindDynamic :: BindHandle -> ErrorHandle -> ContextPtr -> FunPtr OCICallbackInBind -> ContextPtr -> FunPtr OCICallbackOutBind -> IO CInt
type OCICallbackInBind = ContextPtr -> BindHandle -> CInt -> CInt -> Ptr BufferPtr -> CInt -> Ptr Word8 -> Ptr CShort -> IO CInt
type OCICallbackOutBind = ContextPtr -> BindHandle -> CInt -> CInt -> Ptr BufferPtr -> Ptr CInt -> Ptr Word8 -> Ptr CShort -> Ptr (Ptr CShort) -> IO CInt
mkOCICallbackInBind :: OCICallbackInBind -> IO (FunPtr OCICallbackInBind)
mkOCICallbackOutBind :: OCICallbackOutBind -> IO (FunPtr OCICallbackOutBind)
getOCIErrorMsg2 :: OCIHandle -> CInt -> Ptr CInt -> CString -> CInt -> IO (CInt, String)
getOCIErrorMsg :: OCIHandle -> CInt -> IO (CInt, String)
fromEnumOCIErrorCode :: CInt -> String
formatErrorCodeDesc :: CInt -> String -> String
formatOCIMsg :: CInt -> String -> OCIHandle -> CInt -> IO (Int, String)
formatMsgCommon :: OCIException -> OCIHandle -> CInt -> IO (Int, String)
formatErrorMsg :: OCIException -> ErrorHandle -> IO (Int, String)
formatEnvMsg :: OCIException -> EnvHandle -> IO (Int, String)
testForError :: CInt -> String -> a -> IO a
testForErrorWithPtr :: Storable a => CInt -> String -> Ptr a -> IO a
envCreate :: IO EnvHandle
handleAlloc :: CInt -> OCIHandle -> IO OCIHandle
handleFree :: CInt -> OCIHandle -> IO ()
setHandleAttr :: ErrorHandle -> OCIHandle -> CInt -> Ptr a -> CInt -> IO ()
setHandleAttrString :: ErrorHandle -> OCIHandle -> CInt -> String -> CInt -> IO ()
getHandleAttr :: Storable a => ErrorHandle -> OCIHandle -> CInt -> CInt -> IO a
getParam :: ErrorHandle -> StmtHandle -> Int -> IO ParamHandle
dbLogon :: String -> String -> String -> EnvHandle -> ErrorHandle -> IO ConnHandle
dbLogoff :: ErrorHandle -> ConnHandle -> IO ()
terminate :: IO ()
serverDetach :: ErrorHandle -> ServerHandle -> IO ()
serverAttach :: ErrorHandle -> ServerHandle -> String -> IO ()
getSession :: ErrorHandle -> ConnHandle -> IO SessHandle
sessionBegin :: ErrorHandle -> ConnHandle -> SessHandle -> CInt -> IO ()
sessionEnd :: ErrorHandle -> ConnHandle -> SessHandle -> IO ()
beginTrans :: ErrorHandle -> ConnHandle -> CInt -> IO ()
commitTrans :: ErrorHandle -> ConnHandle -> IO ()
rollbackTrans :: ErrorHandle -> ConnHandle -> IO ()
stmtPrepare :: ErrorHandle -> StmtHandle -> String -> IO ()
stmtExecute :: ErrorHandle -> ConnHandle -> StmtHandle -> Int -> IO ()
defineByPos :: ErrorHandle -> StmtHandle -> Int -> Int -> CInt -> IO ColumnInfo
sbph :: String -> Int -> Bool -> String -> String
bindByPos :: ErrorHandle -> StmtHandle -> Int -> CShort -> BufferPtr -> Int -> CInt -> IO ()
bindOutputByPos :: ErrorHandle -> StmtHandle -> Int -> ForeignPtr CShort -> ForeignPtr OCIBuffer -> Int -> CInt -> IO BindHandle
stmtFetch :: ErrorHandle -> StmtHandle -> IO CInt
Documentation
data OCIStruct
  • Each handle type has its own data type, to prevent stupid errors + i.e. using the wrong handle at the wrong time. +
  • In GHC you can simply say data OCIStruct i.e. there's no need for = OCIStruct. + I've decided to be more portable, as it doesn't cost much. +
  • Use castPtr if you need to convert handles (say OCIHandle to a more specific type, or vice versa). +
Constructors
OCIStruct
type OCIHandle = Ptr OCIStruct
data OCIBuffer
Constructors
OCIBuffer
type BufferPtr = Ptr OCIBuffer
type ColumnResultBuffer = ForeignPtr OCIBuffer
data Context
Constructors
Context
type ContextPtr = Ptr Context
data EnvStruct
Constructors
EnvStruct
type EnvHandle = Ptr EnvStruct
data ErrorStruct
Constructors
ErrorStruct
type ErrorHandle = Ptr ErrorStruct
data ServerStruct
Constructors
ServerStruct
type ServerHandle = Ptr ServerStruct
data UserStruct
Constructors
UserStruct
type UserHandle = Ptr UserStruct
data ConnStruct
Constructors
ConnStruct
type ConnHandle = Ptr ConnStruct
data SessStruct
Constructors
SessStruct
type SessHandle = Ptr SessStruct
data StmtStruct
Constructors
StmtStruct
type StmtHandle = Ptr StmtStruct
data DefnStruct
Constructors
DefnStruct
type DefnHandle = Ptr DefnStruct
data ParamStruct
Constructors
ParamStruct
type ParamHandle = Ptr ParamStruct
data BindStruct
Constructors
BindStruct
type BindHandle = Ptr BindStruct
type ColumnInfo = (DefnHandle, ColumnResultBuffer, ForeignPtr CShort, ForeignPtr CShort)
data OCIException
Low-level, OCI library errors. +
Constructors
OCIException CInt String
show/hide Instances
catchOCI :: IO a -> (OCIException -> IO a) -> IO a
throwOCI :: OCIException -> a
mkCInt :: Int -> CInt
mkCShort :: CInt -> CShort
cStrLen :: CStringLen -> CInt
cStr :: CStringLen -> CString
Foreign OCI functions +
ociEnvCreate :: Ptr EnvHandle -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IO CInt
ociHandleAlloc :: OCIHandle -> Ptr OCIHandle -> CInt -> CInt -> Ptr a -> IO CInt
ociHandleFree :: OCIHandle -> CInt -> IO CInt
ociErrorGet :: OCIHandle -> CInt -> CString -> Ptr CInt -> CString -> CInt -> CInt -> IO CInt
ociParamGet :: OCIHandle -> CInt -> ErrorHandle -> Ptr OCIHandle -> CInt -> IO CInt
ociAttrGet :: OCIHandle -> CInt -> BufferPtr -> Ptr CInt -> CInt -> ErrorHandle -> IO CInt
ociAttrSet :: OCIHandle -> CInt -> BufferPtr -> CInt -> CInt -> ErrorHandle -> IO CInt
ociLogon :: EnvHandle -> ErrorHandle -> Ptr ConnHandle -> CString -> CInt -> CString -> CInt -> CString -> CInt -> IO CInt
ociLogoff :: ConnHandle -> ErrorHandle -> IO CInt
ociSessionBegin :: ConnHandle -> ErrorHandle -> SessHandle -> CInt -> CInt -> IO CInt
ociSessionEnd :: ConnHandle -> ErrorHandle -> SessHandle -> CInt -> IO CInt
ociServerAttach :: ServerHandle -> ErrorHandle -> CString -> CInt -> CInt -> IO CInt
ociServerDetach :: ServerHandle -> ErrorHandle -> CInt -> IO CInt
ociTerminate :: CInt -> IO CInt
ociTransStart :: ConnHandle -> ErrorHandle -> Word8 -> CInt -> IO CInt
ociTransCommit :: ConnHandle -> ErrorHandle -> CInt -> IO CInt
ociTransRollback :: ConnHandle -> ErrorHandle -> CInt -> IO CInt
ociStmtPrepare :: StmtHandle -> ErrorHandle -> CString -> CInt -> CInt -> CInt -> IO CInt
ociDefineByPos :: StmtHandle -> Ptr DefnHandle -> ErrorHandle -> CInt -> BufferPtr -> CInt -> CShort -> Ptr CShort -> Ptr CShort -> Ptr CShort -> CInt -> IO CInt
ociStmtExecute :: ConnHandle -> StmtHandle -> ErrorHandle -> CInt -> CInt -> OCIHandle -> OCIHandle -> CInt -> IO CInt
ociStmtFetch :: StmtHandle -> ErrorHandle -> CInt -> CShort -> CInt -> IO CInt
ociBindByPos :: StmtHandle -> Ptr BindHandle -> ErrorHandle -> CUInt -> BufferPtr -> CInt -> CUShort -> Ptr CShort -> Ptr CUShort -> Ptr CUShort -> Ptr CUInt -> Ptr CUInt -> CUInt -> IO CInt
ociBindDynamic :: BindHandle -> ErrorHandle -> ContextPtr -> FunPtr OCICallbackInBind -> ContextPtr -> FunPtr OCICallbackOutBind -> IO CInt
type OCICallbackInBind = ContextPtr -> BindHandle -> CInt -> CInt -> Ptr BufferPtr -> CInt -> Ptr Word8 -> Ptr CShort -> IO CInt
type OCICallbackOutBind = ContextPtr -> BindHandle -> CInt -> CInt -> Ptr BufferPtr -> Ptr CInt -> Ptr Word8 -> Ptr CShort -> Ptr (Ptr CShort) -> IO CInt
mkOCICallbackInBind :: OCICallbackInBind -> IO (FunPtr OCICallbackInBind)
mkOCICallbackOutBind :: OCICallbackOutBind -> IO (FunPtr OCICallbackOutBind)
OCI error reporting +
getOCIErrorMsg2 :: OCIHandle -> CInt -> Ptr CInt -> CString -> CInt -> IO (CInt, String)
This is just an auxiliary function for getOCIErrorMsg. +
getOCIErrorMsg :: OCIHandle -> CInt -> IO (CInt, String)
fromEnumOCIErrorCode :: CInt -> String
formatErrorCodeDesc :: CInt -> String -> String
formatOCIMsg :: CInt -> String -> OCIHandle -> CInt -> IO (Int, String)
Given the two parts of an OCIException (the error number and text) + get the actual error message from the DBMS and construct an error message + from all of these pieces. +
formatMsgCommon :: OCIException -> OCIHandle -> CInt -> IO (Int, String)
We have two format functions: formatEnvMsg takes the EnvHandle, + formatErrorMsg takes the ErrorHandle. + They're just type-safe wrappers for formatMsgCommon. +
formatErrorMsg :: OCIException -> ErrorHandle -> IO (Int, String)
formatEnvMsg :: OCIException -> EnvHandle -> IO (Int, String)
testForError :: CInt -> String -> a -> IO a

The testForError functions are the only places where OCIException is thrown, + so if you want to change or embellish it, your changes will be localised here. + These functions factor out common error handling code + from the OCI wrapper functions that follow. +

Typically an OCI wrapper function would look like: +

 handleAlloc handleType env = alloca ptr -> do
+   rc <- ociHandleAlloc env ptr handleType 0 nullPtr
+   if rc < 0
+     then throwOCI (OCIException rc msg)
+     else return ()
+

where the code from if rc < 0 onwards was identical. + testForError replaces the code from if rc < 0 ... onwards. +

testForErrorWithPtr :: Storable a => CInt -> String -> Ptr a -> IO a
Like testForError but when the value you want to return + is at the end of a pointer. + Either there was an error, in which case the pointer probably isn't valid, + or there is something at the end of the pointer to return. + See dbLogon and getHandleAttr for example usage. +
Allocating Handles (i.e. creating OCI data structures, and memory management) +
envCreate :: IO EnvHandle
handleAlloc :: CInt -> OCIHandle -> IO OCIHandle
handleFree :: CInt -> OCIHandle -> IO ()
setHandleAttr :: ErrorHandle -> OCIHandle -> CInt -> Ptr a -> CInt -> IO ()
setHandleAttrString :: ErrorHandle -> OCIHandle -> CInt -> String -> CInt -> IO ()
getHandleAttr :: Storable a => ErrorHandle -> OCIHandle -> CInt -> CInt -> IO a
getParam :: ErrorHandle -> StmtHandle -> Int -> IO ParamHandle
Connecting and detaching +
dbLogon :: String -> String -> String -> EnvHandle -> ErrorHandle -> IO ConnHandle
The OCI Logon function doesn't behave as you'd expect when the password is due to expire. + ociLogon returns oci_SUCCESS_WITH_INFO, + but the ConnHandle returned is not valid. + In this case we have to change oci_SUCCESS_WITH_INFO + to oci_ERROR, + so that the error handling code will catch it and abort. + I don't know why the handle returned isn't valid, + as the logon process should be able to complete successfully in this case. +
dbLogoff :: ErrorHandle -> ConnHandle -> IO ()
terminate :: IO ()
serverDetach :: ErrorHandle -> ServerHandle -> IO ()
serverAttach :: ErrorHandle -> ServerHandle -> String -> IO ()
getSession :: ErrorHandle -> ConnHandle -> IO SessHandle
Having established a connection (Service Context), now get the Session. + You can have more than one session per connection, + but I haven't implemented it yet. +
sessionBegin :: ErrorHandle -> ConnHandle -> SessHandle -> CInt -> IO ()
sessionEnd :: ErrorHandle -> ConnHandle -> SessHandle -> IO ()
Transactions +
beginTrans :: ErrorHandle -> ConnHandle -> CInt -> IO ()
commitTrans :: ErrorHandle -> ConnHandle -> IO ()
rollbackTrans :: ErrorHandle -> ConnHandle -> IO ()
Issuing queries +
stmtPrepare :: ErrorHandle -> StmtHandle -> String -> IO ()

With the OCI you do queries with these steps: +

  • prepare your statement (it's just a String) - no communication with DBMS +
  • execute it (this sends it to the DBMS for parsing etc) +
  • allocate result set buffers by calling defineByPos for each column +
  • call fetch for each row. +
  • call handleFree for the StmtHandle + (I assume this is the approved way of terminating the query; + the OCI docs aren't explicit about this.) +
stmtExecute :: ErrorHandle -> ConnHandle -> StmtHandle -> Int -> IO ()
defineByPos
:: ErrorHandle
-> StmtHandle
-> IntPosition +
-> IntBuffer size in bytes +
-> CIntSQL Datatype (from Database.Oracle.OCIConstants) +
-> IO ColumnInfotuple: (DefnHandle, Ptr to buffer, Ptr to null indicator, Ptr to size of value in buffer) +

defineByPos allocates memory for a single column value. + The allocated components are: +

  • the result (i.e. value) - you have to say how big with bufsize. +
  • the null indicator (int16) +
  • the size of the returned data (int16) +

Previously it was the caller's responsibility to free the memory after they're done with it. + Now we use mallocForeignPtr, so manual memory management is hopefully + a thing of the past. + The caller will also have to cast the data in bufferptr to the expected type + (using castPtr). +

sbph :: String -> Int -> Bool -> String -> String
bindByPos
:: ErrorHandle
-> StmtHandle
-> IntPosition +
-> CShortNull ind: 0 == not null, -1 == null +
-> BufferPtrpayload +
-> Intpayload size in bytes +
-> CIntSQL Datatype (from Database.Oracle.OCIConstants) +
-> IO ()
bindOutputByPos
:: ErrorHandle
-> StmtHandle
-> IntPosition +
-> ForeignPtr CShortNull ind: 0 == not null, -1 == null +
-> ForeignPtr OCIBufferpayload +
-> Intpayload size in bytes +
-> CIntSQL Datatype (from Database.Oracle.OCIConstants) +
-> IO BindHandle
stmtFetch :: ErrorHandle -> StmtHandle -> IO CInt
stmtFetch takes a lot of wall-clock time + because it involves a network trip to the DBMS for each call. +
Produced by Haddock version 0.7
addfile ./doc/html/Database-Oracle-Test-Enumerator.html hunk ./doc/html/Database-Oracle-Test-Enumerator.html 1 + + +Database.Oracle.Test.Enumerator
 ContentsIndex
Database.Oracle.Test.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Documentation
runTest :: ShouldRunTests -> [String] -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Oracle-Test-OCIFunctions.html hunk ./doc/html/Database-Oracle-Test-OCIFunctions.html 1 + + +Database.Oracle.Test.OCIFunctions
 ContentsIndex
Database.Oracle.Test.OCIFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Test harness for Database.Oracle.OCIFunctions. + This module depends on on Database.Oracle.OCIFunctions. + so it should only use functions from there (and Database.Oracle.OCIConstants). +
Documentation
runTest :: [String] -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-PostgreSQL-Enumerator.html hunk ./doc/html/Database-PostgreSQL-Enumerator.html 1 + + +Database.PostgreSQL.Enumerator
 ContentsIndex
Database.PostgreSQL.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
PostgreSQL implementation of Database.Enumerator. +
Synopsis
data Session
connect :: [ConnectAttr] -> ConnectA Session
data ConnectAttr
= CAhost String
| CAhostaddr String
| CAport String
| CAdbname String
| CAuser String
| CApassword String
| CAconnect_timeout Int
| CAoptions String
| CAsslmode String
| CAservice String
prepareStmt :: String -> QueryString -> [Oid] -> PreparationA Session PreparedStmt
preparePrefetch :: Int -> String -> QueryString -> [Oid] -> PreparationA Session PreparedStmt
sql :: String -> QueryString
sqlbind :: String -> [BindA Session PreparedStmt BindObj] -> QueryStringTuned
prefetch :: Int -> String -> [BindA Session PreparedStmt BindObj] -> QueryStringTuned
bindType :: PGType a => a -> Oid
module Database.Enumerator
Documentation
data Session
show/hide Instances
ISession Session
Command BoundStmt Session
Command QueryString Session
Command String Session
IQuery Query Session ColumnBuffer
Statement BoundStmt Session Query
Statement QueryString Session Query
Statement QueryStringTuned Session Query
Statement String Session Query
DBBind (Maybe a) Session PreparedStmt BindObj => DBBind a Session PreparedStmt BindObj
IPrepared PreparedStmt Session BoundStmt BindObj
Statement (RefCursor String) Session Query
DBBind (Maybe Double) Session PreparedStmt BindObj
DBBind (Maybe Float) Session PreparedStmt BindObj
DBBind (Maybe Int) Session PreparedStmt BindObj
DBBind (Maybe Int64) Session PreparedStmt BindObj
DBBind (Maybe String) Session PreparedStmt BindObj
Show a => DBBind (Maybe a) Session PreparedStmt BindObj
Statement (NextResultSet mark PreparedStmt) Session Query
connect :: [ConnectAttr] -> ConnectA Session
data ConnectAttr
Specify connection options to connect. + You only need to use whatever subset is relevant for your connection. +
Constructors
CAhost String
CAhostaddr String
CAport String
CAdbname String
CAuser String
CApassword String
CAconnect_timeout Int
CAoptions String
CAsslmode String
CAservice String
prepareStmt :: String -> QueryString -> [Oid] -> PreparationA Session PreparedStmt
preparePrefetch :: Int -> String -> QueryString -> [Oid] -> PreparationA Session PreparedStmt
sql :: String -> QueryString
The simplest kind of a statement: no tuning parameters, + all default, little overhead. +
sqlbind :: String -> [BindA Session PreparedStmt BindObj] -> QueryStringTuned
prefetch :: Int -> String -> [BindA Session PreparedStmt BindObj] -> QueryStringTuned
bindType :: PGType a => a -> Oid
bindType is useful when constructing the list of Oids for stmtPrepare. + You don't need to pass the actual bind values, just dummy values + of the same type (the value isn't used, so undefined is OK here). +
module Database.Enumerator
Produced by Haddock version 0.7
addfile ./doc/html/Database-PostgreSQL-PGFunctions.html hunk ./doc/html/Database-PostgreSQL-PGFunctions.html 1 + + +Database.PostgreSQL.PGFunctions
 ContentsIndex
Database.PostgreSQL.PGFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Simple wrappers for PostgreSQL functions (FFI) plus middle-level + wrappers (in the second part of this file) +
Synopsis
data DBHandleStruct = PGconn
type DBHandle = Ptr DBHandleStruct
data StmtStruct = PGresult
type ResultSetHandle = Ptr StmtStruct
type Oid = CUInt
type Format = CInt
type Void = ()
type ParamLen = CInt
data PGException = PGException Int String
catchPG :: IO a -> (PGException -> IO a) -> IO a
throwPG :: Integral a => a -> String -> any
rethrowPG :: PGException -> any
cStr :: CStringLen -> CString
cStrLen :: CStringLen -> CInt
fPQconnectdb :: CString -> IO DBHandle
fPQfinish :: DBHandle -> IO ()
fPQreset :: DBHandle -> IO ()
fPQdb :: DBHandle -> CString
type ConnStatusType = CInt
fPQstatus :: DBHandle -> IO ConnStatusType
fPQerrorMessage :: DBHandle -> IO CString
type NoticeReceiver = Ptr () -> ResultSetHandle -> IO ()
type NoticeProcessor = Ptr () -> CString -> IO ()
mkNoticeReceiver :: NoticeReceiver -> IO (FunPtr NoticeReceiver)
mkNoticeProcessor :: NoticeProcessor -> IO (FunPtr NoticeProcessor)
fPQsetNoticeReceiver :: DBHandle -> FunPtr NoticeReceiver -> Ptr () -> IO (FunPtr NoticeReceiver)
fPQsetNoticeProcessor :: DBHandle -> FunPtr NoticeProcessor -> Ptr () -> IO (FunPtr NoticeProcessor)
fPQexecParams :: DBHandle -> CString -> CInt -> Ptr Oid -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle
fPQprepare :: DBHandle -> CString -> CString -> CInt -> Ptr Oid -> IO ResultSetHandle
fPQexecPrepared :: DBHandle -> CString -> CInt -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle
fPQresultStatus :: ResultSetHandle -> IO ExecStatusType
type ExecStatusType = CInt
fPQresultErrorMessage :: ResultSetHandle -> IO CString
fPQclear :: ResultSetHandle -> IO ()
fPQntuples :: ResultSetHandle -> IO CInt
fPQnfields :: ResultSetHandle -> IO CInt
fPQfname :: ResultSetHandle -> CInt -> IO CString
fPQfformat :: ResultSetHandle -> CInt -> IO CInt
fPQftype :: ResultSetHandle -> CInt -> IO Oid
fPQgetvalue :: ResultSetHandle -> CInt -> CInt -> IO (Ptr Word8)
fPQgetisnull :: ResultSetHandle -> CInt -> CInt -> IO CInt
fPQgetlength :: ResultSetHandle -> CInt -> CInt -> IO CInt
fPQcmdStatus :: ResultSetHandle -> IO CString
fPQcmdTuples :: ResultSetHandle -> IO CString
fPQoidValue :: ResultSetHandle -> IO Oid
type PGVerbosity = CInt
fPQsetErrorVerbosity :: DBHandle -> PGVerbosity -> IO PGVerbosity
getError :: DBHandle -> IO String
openDb :: String -> IO DBHandle
closeDb :: DBHandle -> IO ()
class PGType a where
pgTypeFormat :: a -> Format
pgTypeOid :: a -> Oid
pgNewValue :: a -> IO (Ptr Word8)
pgPeek :: Ptr Word8 -> IO a
pgSize :: a -> Int
data PGBindVal = PGBindVal {
bindValOid :: Oid
bindValFormat :: Format
bindValSize :: CInt
bindValPtr :: (IO (Ptr Word8))
}
newBinaryValue :: (Storable a, PGType b) => (b -> a) -> b -> IO (Ptr Word8)
peekValueRev :: (Storable a, PGType b) => b -> (a -> b) -> Ptr Word8 -> IO b
reverseBytes :: Int -> Ptr Word8 -> Ptr Word8 -> IO ()
reverseBytes' :: Int -> Ptr Word8 -> Ptr Word8 -> IO ()
toCInt :: Int -> CInt
fromCInt :: CInt -> Int
toCInt16 :: Int16 -> CShort
fromCInt16 :: CShort -> Int16
toCInt32 :: Int32 -> CInt
fromCInt32 :: CInt -> Int32
toCInt64 :: Int64 -> CLLong
fromCInt64 :: CLLong -> Int64
toCChar :: Char -> CChar
fromCChar :: CChar -> Char
toCDouble :: Double -> CDouble
fromCDouble :: CDouble -> Double
toCFloat :: Float -> CFloat
fromCFloat :: CFloat -> Float
check'stmt :: DBHandle -> ExecStatusType -> ResultSetHandle -> IO ResultSetHandle
stmtPrepare :: DBHandle -> String -> String -> [Oid] -> IO String
nqExec :: DBHandle -> String -> IO (String, String, Oid)
execCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid)
execPreparedCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid)
stmtExecImm :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int)
stmtExec0 :: DBHandle -> String -> IO (ResultSetHandle, Int)
stmtExec :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int)
execPrepared :: DBHandle -> String -> [PGBindVal] -> CInt -> IO (ResultSetHandle, Int)
prepare'n'exec :: DBHandle -> String -> String -> [PGBindVal] -> IO (ResultSetHandle, Int)
stmtFinalise :: ResultSetHandle -> IO ()
colValPtr :: ResultSetHandle -> Int -> Int -> IO (Ptr Word8)
colVal :: (Read a, PGType a) => ResultSetHandle -> Int -> Int -> IO a
colValString :: ResultSetHandle -> Int -> Int -> IO String
colValInt :: ResultSetHandle -> Int -> Int -> IO Int
colValInt64 :: ResultSetHandle -> Int -> Int -> IO Int64
colValDouble :: ResultSetHandle -> Int -> Int -> IO Double
colValFloat :: ResultSetHandle -> Int -> Int -> IO Float
colValNull :: ResultSetHandle -> Int -> Int -> IO Bool
sbph :: String -> Int -> Bool -> String -> String
Documentation
data DBHandleStruct
Constructors
PGconn
type DBHandle = Ptr DBHandleStruct
data StmtStruct
Constructors
PGresult
type ResultSetHandle = Ptr StmtStruct
type Oid = CUInt
type Format = CInt
type Void = ()
type ParamLen = CInt
data PGException
Constructors
PGException Int String
show/hide Instances
catchPG :: IO a -> (PGException -> IO a) -> IO a
throwPG :: Integral a => a -> String -> any
rethrowPG :: PGException -> any
cStr :: CStringLen -> CString
cStrLen :: CStringLen -> CInt
fPQconnectdb :: CString -> IO DBHandle
fPQfinish :: DBHandle -> IO ()
fPQreset :: DBHandle -> IO ()
fPQdb :: DBHandle -> CString
type ConnStatusType = CInt
fPQstatus :: DBHandle -> IO ConnStatusType
fPQerrorMessage :: DBHandle -> IO CString
type NoticeReceiver = Ptr () -> ResultSetHandle -> IO ()
type NoticeProcessor = Ptr () -> CString -> IO ()
mkNoticeReceiver :: NoticeReceiver -> IO (FunPtr NoticeReceiver)
mkNoticeProcessor :: NoticeProcessor -> IO (FunPtr NoticeProcessor)
fPQsetNoticeReceiver :: DBHandle -> FunPtr NoticeReceiver -> Ptr () -> IO (FunPtr NoticeReceiver)
fPQsetNoticeProcessor :: DBHandle -> FunPtr NoticeProcessor -> Ptr () -> IO (FunPtr NoticeProcessor)
fPQexecParams :: DBHandle -> CString -> CInt -> Ptr Oid -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle
fPQprepare :: DBHandle -> CString -> CString -> CInt -> Ptr Oid -> IO ResultSetHandle
fPQexecPrepared :: DBHandle -> CString -> CInt -> Ptr Void -> Ptr ParamLen -> Ptr Format -> CInt -> IO ResultSetHandle
fPQresultStatus :: ResultSetHandle -> IO ExecStatusType
type ExecStatusType = CInt
fPQresultErrorMessage :: ResultSetHandle -> IO CString
fPQclear :: ResultSetHandle -> IO ()
fPQntuples :: ResultSetHandle -> IO CInt
fPQnfields :: ResultSetHandle -> IO CInt
fPQfname :: ResultSetHandle -> CInt -> IO CString
fPQfformat :: ResultSetHandle -> CInt -> IO CInt
fPQftype :: ResultSetHandle -> CInt -> IO Oid
fPQgetvalue :: ResultSetHandle -> CInt -> CInt -> IO (Ptr Word8)
fPQgetisnull :: ResultSetHandle -> CInt -> CInt -> IO CInt
fPQgetlength :: ResultSetHandle -> CInt -> CInt -> IO CInt
fPQcmdStatus :: ResultSetHandle -> IO CString
fPQcmdTuples :: ResultSetHandle -> IO CString
fPQoidValue :: ResultSetHandle -> IO Oid
type PGVerbosity = CInt
fPQsetErrorVerbosity :: DBHandle -> PGVerbosity -> IO PGVerbosity
getError :: DBHandle -> IO String
openDb :: String -> IO DBHandle
closeDb :: DBHandle -> IO ()
class PGType a where
Methods
pgTypeFormat :: a -> Format
pgTypeOid :: a -> Oid
pgNewValue :: a -> IO (Ptr Word8)
pgPeek :: Ptr Word8 -> IO a
pgSize :: a -> Int
show/hide Instances
data PGBindVal
Constructors
PGBindVal
bindValOid :: Oid
bindValFormat :: Format
bindValSize :: CInt
bindValPtr :: (IO (Ptr Word8))
newBinaryValue :: (Storable a, PGType b) => (b -> a) -> b -> IO (Ptr Word8)
peekValueRev :: (Storable a, PGType b) => b -> (a -> b) -> Ptr Word8 -> IO b
reverseBytes :: Int -> Ptr Word8 -> Ptr Word8 -> IO ()
reverseBytes' :: Int -> Ptr Word8 -> Ptr Word8 -> IO ()
toCInt :: Int -> CInt
fromCInt :: CInt -> Int
toCInt16 :: Int16 -> CShort
fromCInt16 :: CShort -> Int16
toCInt32 :: Int32 -> CInt
fromCInt32 :: CInt -> Int32
toCInt64 :: Int64 -> CLLong
fromCInt64 :: CLLong -> Int64
toCChar :: Char -> CChar
fromCChar :: CChar -> Char
toCDouble :: Double -> CDouble
fromCDouble :: CDouble -> Double
toCFloat :: Float -> CFloat
fromCFloat :: CFloat -> Float
check'stmt :: DBHandle -> ExecStatusType -> ResultSetHandle -> IO ResultSetHandle
stmtPrepare :: DBHandle -> String -> String -> [Oid] -> IO String
nqExec :: DBHandle -> String -> IO (String, String, Oid)
execCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid)
execPreparedCommand :: DBHandle -> String -> [PGBindVal] -> IO (String, String, Oid)
stmtExecImm :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int)
stmtExec0 :: DBHandle -> String -> IO (ResultSetHandle, Int)
stmtExec :: DBHandle -> String -> [PGBindVal] -> IO (ResultSetHandle, Int)
execPrepared :: DBHandle -> String -> [PGBindVal] -> CInt -> IO (ResultSetHandle, Int)
prepare'n'exec :: DBHandle -> String -> String -> [PGBindVal] -> IO (ResultSetHandle, Int)
stmtFinalise :: ResultSetHandle -> IO ()
colValPtr :: ResultSetHandle -> Int -> Int -> IO (Ptr Word8)
Column numbers are zero-indexed, so subtract one + from given index (we present a one-indexed interface). + So are the row numbers. +
colVal :: (Read a, PGType a) => ResultSetHandle -> Int -> Int -> IO a
colValString :: ResultSetHandle -> Int -> Int -> IO String
colValInt :: ResultSetHandle -> Int -> Int -> IO Int
colValInt64 :: ResultSetHandle -> Int -> Int -> IO Int64
colValDouble :: ResultSetHandle -> Int -> Int -> IO Double
colValFloat :: ResultSetHandle -> Int -> Int -> IO Float
colValNull :: ResultSetHandle -> Int -> Int -> IO Bool
sbph :: String -> Int -> Bool -> String -> String
Produced by Haddock version 0.7
addfile ./doc/html/Database-PostgreSQL-Test-Enumerator.html hunk ./doc/html/Database-PostgreSQL-Test-Enumerator.html 1 + + +Database.PostgreSQL.Test.Enumerator
 ContentsIndex
Database.PostgreSQL.Test.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Documentation
runTest :: ShouldRunTests -> [String] -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-PostgreSQL-Test-PGFunctions.html hunk ./doc/html/Database-PostgreSQL-Test-PGFunctions.html 1 + + +Database.PostgreSQL.Test.PGFunctions
 ContentsIndex
Database.PostgreSQL.Test.PGFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Documentation
runTest :: String -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Sqlite-Enumerator.html hunk ./doc/html/Database-Sqlite-Enumerator.html 1 + + +Database.Sqlite.Enumerator
 ContentsIndex
Database.Sqlite.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Sqlite implementation of Database.Enumerator. +
Documentation
data Session
show/hide Instances
ISession Session
Command BoundStmt Session
Command QueryString Session
Command StmtBind Session
Command String Session
IQuery Query Session ColumnBuffer
Statement BoundStmt Session Query
Statement PreparedStmt Session Query
Statement QueryString Session Query
Statement StmtBind Session Query
Statement String Session Query
DBBind (Maybe a) Session PreparedStmt BindObj => DBBind a Session PreparedStmt BindObj
IPrepared PreparedStmt Session BoundStmt BindObj
DBBind (Maybe CalendarTime) Session PreparedStmt BindObj
DBBind (Maybe Double) Session PreparedStmt BindObj
DBBind (Maybe Int) Session PreparedStmt BindObj
DBBind (Maybe Int64) Session PreparedStmt BindObj
DBBind (Maybe String) Session PreparedStmt BindObj
Show a => DBBind (Maybe a) Session PreparedStmt BindObj
connect :: String -> ConnectA Session
prepareStmt :: QueryString -> PreparationA Session PreparedStmt
sql :: String -> QueryString
sqlbind :: String -> [BindA Session PreparedStmt BindObj] -> StmtBind
prefetch :: Int -> String -> [BindA Session PreparedStmt BindObj] -> StmtBind
module Database.Enumerator
Produced by Haddock version 0.7
addfile ./doc/html/Database-Sqlite-SqliteFunctions.html hunk ./doc/html/Database-Sqlite-SqliteFunctions.html 1 + + +Database.Sqlite.SqliteFunctions
 ContentsIndex
Database.Sqlite.SqliteFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Simple wrappers for Sqlite functions (FFI). +
Synopsis
data DBHandleStruct = DBHandleStruct
type DBHandle = Ptr DBHandleStruct
data StmtStruct = StmtStruct
type StmtHandle = Ptr StmtStruct
type Blob = Ptr Word8
type SqliteCallback a = FunPtr (Ptr a -> CInt -> Ptr CString -> Ptr CString -> IO Int)
type FreeFunPtr = FunPtr (Ptr Word8 -> IO ())
data SqliteException = SqliteException Int String
catchSqlite :: IO a -> (SqliteException -> IO a) -> IO a
throwSqlite :: SqliteException -> a
sqliteOK :: CInt
sqliteERROR :: CInt
sqliteROW :: CInt
sqliteDONE :: CInt
cStr :: CStringLen -> CString
cStrLen :: CStringLen -> CInt
type UTF16CString = CString
type UTF8CString = CString
sqliteOpen :: UTF8CString -> Ptr DBHandle -> IO CInt
sqliteClose :: DBHandle -> IO CInt
sqlitePrepare :: DBHandle -> UTF8CString -> CInt -> Ptr StmtHandle -> Ptr CString -> IO CInt
sqliteExec :: DBHandle -> UTF8CString -> SqliteCallback a -> Ptr a -> Ptr CString -> IO CInt
sqliteStep :: StmtHandle -> IO CInt
sqliteFinalise :: StmtHandle -> IO CInt
sqliteReset :: StmtHandle -> IO CInt
sqliteChanges :: DBHandle -> IO CInt
sqliteFree :: Ptr a -> IO ()
sqliteErrcode :: DBHandle -> IO CInt
sqliteErrmsg :: DBHandle -> IO UTF8CString
sqliteColumnBytes :: StmtHandle -> CInt -> IO Int
sqliteColumnBlob :: StmtHandle -> CInt -> IO Blob
sqliteColumnDouble :: StmtHandle -> CInt -> IO CDouble
sqliteColumnInt :: StmtHandle -> CInt -> IO CInt
sqliteColumnInt64 :: StmtHandle -> CInt -> IO CLLong
sqliteColumnText :: StmtHandle -> CInt -> IO UTF8CString
sqliteColumnText16 :: StmtHandle -> CInt -> IO UTF16CString
sqliteBindBlob :: StmtHandle -> CInt -> Blob -> CInt -> FreeFunPtr -> IO CInt
sqliteBindDouble :: StmtHandle -> CInt -> CDouble -> IO CInt
sqliteBindInt :: StmtHandle -> CInt -> CInt -> IO CInt
sqliteBindInt64 :: StmtHandle -> CInt -> CLLong -> IO CInt
sqliteBindNull :: StmtHandle -> CInt -> IO CInt
sqliteBindText :: StmtHandle -> CInt -> UTF8CString -> CInt -> FreeFunPtr -> IO CInt
sqliteBindText16 :: StmtHandle -> CInt -> UTF16CString -> CInt -> FreeFunPtr -> IO CInt
getError :: DBHandle -> IO SqliteException
getAndRaiseError :: Int -> DBHandle -> IO a
errorTest :: DBHandle -> CInt -> IO a -> IO a
testForError :: DBHandle -> CInt -> a -> IO a
testForErrorWithPtr :: Storable a => DBHandle -> CInt -> Ptr a -> IO a
openDb :: String -> IO DBHandle
closeDb :: DBHandle -> IO ()
stmtExec :: DBHandle -> String -> IO Int
stmtChanges :: DBHandle -> IO Int
stmtPrepare :: DBHandle -> String -> IO StmtHandle
stmtFetch :: DBHandle -> StmtHandle -> IO CInt
stmtFinalise :: DBHandle -> StmtHandle -> IO ()
stmtReset :: DBHandle -> StmtHandle -> IO ()
colValInt :: StmtHandle -> Int -> IO Int
colValInt64 :: StmtHandle -> Int -> IO Int64
colValDouble :: StmtHandle -> Int -> IO Double
colValString :: StmtHandle -> Int -> IO (Maybe String)
colValBlob :: StmtHandle -> Int -> IO (ForeignPtr Blob)
bindDouble :: DBHandle -> StmtHandle -> Int -> Double -> IO ()
bindInt :: DBHandle -> StmtHandle -> Int -> Int -> IO ()
bindInt64 :: DBHandle -> StmtHandle -> Int -> Int64 -> IO ()
bindNull :: DBHandle -> StmtHandle -> Int -> IO ()
bindString :: DBHandle -> StmtHandle -> Int -> String -> IO ()
bindBlob :: DBHandle -> StmtHandle -> Int -> Blob -> Int -> IO ()
Documentation
data DBHandleStruct
Constructors
DBHandleStruct
type DBHandle = Ptr DBHandleStruct
data StmtStruct
Constructors
StmtStruct
type StmtHandle = Ptr StmtStruct
type Blob = Ptr Word8
type SqliteCallback a = FunPtr (Ptr a -> CInt -> Ptr CString -> Ptr CString -> IO Int)
type FreeFunPtr = FunPtr (Ptr Word8 -> IO ())
data SqliteException
Constructors
SqliteException Int String
show/hide Instances
catchSqlite :: IO a -> (SqliteException -> IO a) -> IO a
throwSqlite :: SqliteException -> a
sqliteOK :: CInt
sqliteERROR :: CInt
sqliteROW :: CInt
sqliteDONE :: CInt
cStr :: CStringLen -> CString
cStrLen :: CStringLen -> CInt
type UTF16CString = CString
type UTF8CString = CString
sqliteOpen :: UTF8CString -> Ptr DBHandle -> IO CInt
sqliteClose :: DBHandle -> IO CInt
sqlitePrepare :: DBHandle -> UTF8CString -> CInt -> Ptr StmtHandle -> Ptr CString -> IO CInt
sqliteExec :: DBHandle -> UTF8CString -> SqliteCallback a -> Ptr a -> Ptr CString -> IO CInt
sqliteStep :: StmtHandle -> IO CInt
sqliteFinalise :: StmtHandle -> IO CInt
sqliteReset :: StmtHandle -> IO CInt
sqliteChanges :: DBHandle -> IO CInt
sqliteFree :: Ptr a -> IO ()
sqliteErrcode :: DBHandle -> IO CInt
sqliteErrmsg :: DBHandle -> IO UTF8CString
sqliteColumnBytes :: StmtHandle -> CInt -> IO Int
sqliteColumnBlob :: StmtHandle -> CInt -> IO Blob
sqliteColumnDouble :: StmtHandle -> CInt -> IO CDouble
sqliteColumnInt :: StmtHandle -> CInt -> IO CInt
sqliteColumnInt64 :: StmtHandle -> CInt -> IO CLLong
sqliteColumnText :: StmtHandle -> CInt -> IO UTF8CString
sqliteColumnText16 :: StmtHandle -> CInt -> IO UTF16CString
sqliteBindBlob :: StmtHandle -> CInt -> Blob -> CInt -> FreeFunPtr -> IO CInt
sqliteBindDouble :: StmtHandle -> CInt -> CDouble -> IO CInt
sqliteBindInt :: StmtHandle -> CInt -> CInt -> IO CInt
sqliteBindInt64 :: StmtHandle -> CInt -> CLLong -> IO CInt
sqliteBindNull :: StmtHandle -> CInt -> IO CInt
sqliteBindText :: StmtHandle -> CInt -> UTF8CString -> CInt -> FreeFunPtr -> IO CInt
sqliteBindText16 :: StmtHandle -> CInt -> UTF16CString -> CInt -> FreeFunPtr -> IO CInt
getError :: DBHandle -> IO SqliteException
getAndRaiseError :: Int -> DBHandle -> IO a
errorTest :: DBHandle -> CInt -> IO a -> IO a
testForError :: DBHandle -> CInt -> a -> IO a
testForErrorWithPtr :: Storable a => DBHandle -> CInt -> Ptr a -> IO a
openDb :: String -> IO DBHandle
closeDb :: DBHandle -> IO ()
stmtExec :: DBHandle -> String -> IO Int
stmtChanges :: DBHandle -> IO Int
stmtPrepare :: DBHandle -> String -> IO StmtHandle
stmtFetch :: DBHandle -> StmtHandle -> IO CInt
stmtFinalise :: DBHandle -> StmtHandle -> IO ()
stmtReset :: DBHandle -> StmtHandle -> IO ()
colValInt :: StmtHandle -> Int -> IO Int
Column numbers are zero-indexed, so subtract one + from given index (we present a one-indexed interface). +
colValInt64 :: StmtHandle -> Int -> IO Int64
colValDouble :: StmtHandle -> Int -> IO Double
colValString :: StmtHandle -> Int -> IO (Maybe String)
colValBlob :: StmtHandle -> Int -> IO (ForeignPtr Blob)
bindDouble :: DBHandle -> StmtHandle -> Int -> Double -> IO ()
bindInt :: DBHandle -> StmtHandle -> Int -> Int -> IO ()
bindInt64 :: DBHandle -> StmtHandle -> Int -> Int64 -> IO ()
bindNull :: DBHandle -> StmtHandle -> Int -> IO ()
bindString :: DBHandle -> StmtHandle -> Int -> String -> IO ()
bindBlob :: DBHandle -> StmtHandle -> Int -> Blob -> Int -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Sqlite-Test-Enumerator.html hunk ./doc/html/Database-Sqlite-Test-Enumerator.html 1 + + +Database.Sqlite.Test.Enumerator
 ContentsIndex
Database.Sqlite.Test.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Documentation
runTest :: ShouldRunTests -> [String] -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Sqlite-Test-SqliteFunctions.html hunk ./doc/html/Database-Sqlite-Test-SqliteFunctions.html 1 + + +Database.Sqlite.Test.SqliteFunctions
 ContentsIndex
Database.Sqlite.Test.SqliteFunctions
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Documentation
runTest :: String -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Stub-Enumerator.html hunk ./doc/html/Database-Stub-Enumerator.html 1 + + +Database.Stub.Enumerator
 ContentsIndex
Database.Stub.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description

Stub implementation of Database.Enumerator. + Useful for people who can't or won't install a DBMS, + so that they can try out the Enumerator interface. +

Currently last last row of any fetch will have a null in its Int columns + (this makes it easier to test handling of nulls and DBUnexpectedNull). + See fetchIntVal. +

Synopsis
data Session
data ConnParm = ConnParm {
user, pswd, dbname :: String
}
connect :: ConnParm -> ConnectA Session
sql :: String -> QueryString
data QueryResourceUsage = QueryResourceUsage {
prefetchRowCount :: Int
}
sql_tuned :: QueryResourceUsage -> String -> QueryStringTuned
Documentation
data Session
show/hide Instances
ISession Session
Command QueryString Session
Command QueryStringTuned Session
IQuery Query Session ColumnBuffer
Statement QueryString Session Query
Statement QueryStringTuned Session Query
data ConnParm
Constructors
ConnParm
user, pswd, dbname :: String
connect :: ConnParm -> ConnectA Session
sql :: String -> QueryString
data QueryResourceUsage
At present the only resource tuning we support is the number of rows + prefetched by the FFI library. + We use a record to (hopefully) make it easy to add other + tuning parameters later. +
Constructors
QueryResourceUsage
prefetchRowCount :: Int
sql_tuned :: QueryResourceUsage -> String -> QueryStringTuned
Produced by Haddock version 0.7
addfile ./doc/html/Database-Stub-Test-Enumerator.html hunk ./doc/html/Database-Stub-Test-Enumerator.html 1 + + +Database.Stub.Test.Enumerator
 ContentsIndex
Database.Stub.Test.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Simple test harness for Stub. + Stub can't share the tests for "real" backends because it + returns a somewhat contrived result set. +
Documentation
runTest :: a -> [String] -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Test-Enumerator.html hunk ./doc/html/Database-Test-Enumerator.html 1 + + +Database.Test.Enumerator
 ContentsIndex
Database.Test.Enumerator
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Simple test harness. Demonstrates possible usage. +
Documentation
class DBLiteralValue a where
Methods
literalDate :: a -> Int64 -> String
literalInt :: a -> Int -> String
literalInt64 :: a -> Int64 -> String
literalFloat :: a -> Float -> String
literalDouble :: a -> Double -> String
show/hide Instances
data SqliteFunctions
Constructors
SqliteFunctions
show/hide Instances
data OracleFunctions
Constructors
OracleFunctions
show/hide Instances
data PGSqlFunctions
Constructors
PGSqlFunctions
show/hide Instances
dateSqlite :: Int64 -> String
dateOracle :: Int64 -> String
datePG :: Int64 -> String
zeroPad :: Int -> Int64 -> String
makeCalTime :: Int64 -> CalendarTime
expectFloatsAndInts :: [(Double, Int)]
iterNullString :: Monad m => String -> String -> Maybe String -> IterAct m [(String, String, Maybe String)]
iterEmptyString :: Monad m => String -> String -> Maybe String -> IterAct m [(String, String, Maybe String)]
iterUnhandledNull :: Monad m => String -> String -> CalendarTime -> IterAct m [(String, String, CalendarTime)]
iterNullDate :: Monad m => String -> String -> Maybe CalendarTime -> IterAct m [(String, String, CalendarTime)]
iterDate :: Monad m => CalendarTime -> IterAct m [CalendarTime]
iterBoundaryDates :: Monad m => CalendarTime -> IterAct m [CalendarTime]
iterCursor :: Monad m => Int -> IterAct m [Int]
iterBindString :: Monad m => String -> IterAct m [String]
iterBindInt :: Monad m => Int -> IterAct m [Int]
expectBindInt :: [Int]
iterBindIntDoubleString :: Monad m => Int -> Double -> String -> IterAct m [(Int, Double, String)]
expectBindIntDoubleString :: [(Int, Double, String)]
iterBindDate :: Monad m => CalendarTime -> IterAct m [CalendarTime]
data MyTree a
Constructors
Leaf a
Branch [MyTree a]
show/hide Instances
(Eq a, ??? a) => Eq (MyTree a)
(Read a, ??? a) => Read (MyTree a)
(Show a, ??? a) => Show (MyTree a)
iterPolymorphicFetch :: Monad m => MyTree String -> IterAct m (MyTree String)
iterPolymorphicFetchNull :: Monad m => Maybe (MyTree String) -> IterAct m (Maybe (MyTree String))
expectPolymorphicFetchNull :: Maybe (MyTree String)
expectRebind1 :: [Int]
expectRebind2 :: [Int]
Produced by Haddock version 0.7
addfile ./doc/html/Database-Test-MultiConnect.html hunk ./doc/html/Database-Test-MultiConnect.html 1 + + +Database.Test.MultiConnect
 ContentsIndex
Database.Test.MultiConnect
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Tests Database.Enumerator code in the context of multiple + database connections to different DBMS products. + We should add tests to shift data between databases, too. +
Documentation
runTest :: ShouldRunTests -> [String] -> IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Database-Test-Performance.html hunk ./doc/html/Database-Test-Performance.html 1 + + +Database.Test.Performance
 ContentsIndex
Database.Test.Performance
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description
Performance tests. Currently just tests large result sets. +
Synopsis
data ShouldRunTests
= RunTests
| Don'tRunTests
rowCounter :: Monad m => Int -> Int -> IterAct m Int
sqlRows2Power17 :: String
sqlRows2Power20 :: String
Documentation
data ShouldRunTests
Constructors
RunTests
Don'tRunTests
show/hide Instances
rowCounter :: Monad m => Int -> Int -> IterAct m Int
This counter takes the maximum number of rows to fetch as its first argument, + so don't forget to curry it when using it as an iteratee function. + We also try to ensure that it is strict in the counter; + we don't want thousands or millions of unevaluated + thunks sitting + on the stack. +
sqlRows2Power17 :: String
sqlRows2Power20 :: String
Produced by Haddock version 0.7
addfile ./doc/html/Foreign-C-Unicode.html hunk ./doc/html/Foreign-C-Unicode.html 1 + + +Foreign.C.Unicode
 ContentsIndex
Foreign.C.Unicode
Portabilityportable
Stabilityexperimental
Maintaineralistair@abayley.org
Description

Functions to convert various Unicode encodings + into Haskell Strings (at present we only handle UTF-8, + but we'd like to add UTF-16 and UTF-32). +

We assume that the UTF-8 encoded String is a list of + Chars where, for each char c, 0 <= ord c <= 255. + When we convert a Haskell String into a UTF-8 string, + again the Chars in the resulting String are all + codepoints from 0 to 255. +

Synopsis
peekUTF8String :: CString -> IO String
newUTF8String :: String -> IO CString
withUTF8String :: String -> (CString -> IO a) -> IO a
withUTF8StringLen :: String -> (CStringLen -> IO a) -> IO a
toUTF8 :: String -> String
fromUTF8 :: Monad m => String -> m String
fromUTF8E :: String -> Either String String
fromUTF8WE :: Monad m => String -> m String
Documentation
peekUTF8String :: CString -> IO String
Analogous to peekCString. Converts UTF8 CString to String. +
newUTF8String :: String -> IO CString
Analogous to newCString. Creates UTF8 encoded CString. +
withUTF8String :: String -> (CString -> IO a) -> IO a
Analogous to withCString. Creates UTF8 encoded CString. +
withUTF8StringLen :: String -> (CStringLen -> IO a) -> IO a
Analogous to withCStringLen. +
toUTF8 :: String -> String
Converts a String into its UTF8 representation. +
fromUTF8 :: Monad m => String -> m String
We really want a fromUTF8 that will do error recovery + i.e. it will never raise an error, and do the best job it can, + inserting substitution characters where necessary. + But for now we'll just pretend... +
fromUTF8E :: String -> Either String String
Instance of Control.Monad.MonadError, as suggested below. +
fromUTF8WE :: Monad m => String -> m String

Converts a UTF8 representation of a String back into the String, + catching all possible format errors. +

Example: With the Haskell module Control.Monad.Error, you can + instance this as + (fromUTF8WE :: String -> Either String String) + to get a conversion function which either succeeds (Right) or + returns an error message (Left). +

Produced by Haddock version 0.7
addfile ./doc/html/Main.html hunk ./doc/html/Main.html 1 + + +Main
 ContentsIndex
Main
Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Description

Simple driver module, mainly for testing. + Imports test modules and runs test suites. +

This project is now hosted at haskell.org: +

darcs get http://darcs.haskell.org/takusen/main

Currently this is a source-only distribution; + we haven't cabalised it yet. +

Invoke main like this (assuming compiled to takusen.exe): +

 takusen stub noperf
+ takusen sqlite noperf "" "" dbname
+ takusen oracle noperf "" "" dbname  -- no username, so os-authenticated
+ takusen mssql noperf user paswd dbname
+
Documentation
main :: IO ()
Produced by Haddock version 0.7
addfile ./doc/html/Test-MiniUnit.html hunk ./doc/html/Test-MiniUnit.html 1 + + +Test.MiniUnit
 ContentsIndex
Test.MiniUnit
Portabilityportable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org
Contents
exposed for self-testing only; see MiniUnitTest +
Description
This is just a simple one-module unit tets framework, with the same + API as HUnit (albeit with a lot of stuff missing). + We use it because it works in CaughtMonadIO + instead of IO + (and because I couldn't convert HUnit to use CaughtMonadIO). +
Synopsis
runTestTT :: CaughtMonadIO m => String -> [m ()] -> m Int
assertFailure :: CaughtMonadIO m => String -> m ()
assertBool :: CaughtMonadIO m => String -> Bool -> m ()
assertString :: CaughtMonadIO m => String -> m ()
assertEqual :: (Eq a, Show a, CaughtMonadIO m) => String -> a -> a -> m ()
data TestResult
= TestSuccess
| TestFailure String
| TestException String
throwUserError :: CaughtMonadIO m => String -> m ()
runSingleTest :: CaughtMonadIO m => m () -> m TestResult
Documentation
runTestTT :: CaughtMonadIO m => String -> [m ()] -> m Int
Return 0 if everything is rosy, + 1 if there were assertion failures (but no exceptions), + 2 if there were any exceptions. + You could use this return code as the return code from + your program, if you're driving from the command line. +
assertFailure :: CaughtMonadIO m => String -> m ()
assertBool :: CaughtMonadIO m => String -> Bool -> m ()
assertString :: CaughtMonadIO m => String -> m ()
assertEqual
:: (Eq a, Show a, CaughtMonadIO m)
=> Stringmessage preface +
-> aexpected +
-> aactual +
-> m ()
exposed for self-testing only; see MiniUnitTest +
data TestResult
Constructors
TestSuccess
TestFailure String
TestException String
show/hide Instances
throwUserError :: CaughtMonadIO m => String -> m ()
runSingleTest :: CaughtMonadIO m => m () -> m TestResult
Produced by Haddock version 0.7
addfile ./doc/html/Test-MiniUnitTest.html hunk ./doc/html/Test-MiniUnitTest.html 1 + + +Test.MiniUnitTest
 ContentsIndex
Test.MiniUnitTest
Documentation
main :: IO ()
Produced by Haddock version 0.7
addfile ./doc/html/doc-index-A.html hunk ./doc/html/doc-index-A.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (A)
allocBufferFor
assertBool
assertEqual
assertFailure
assertString
addfile ./doc/html/doc-index-B.html hunk ./doc/html/doc-index-B.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (B)
BindA
1 (Type/Class)
2 (Data Constructor)
BindHandle
BindStruct
1 (Type/Class)
2 (Data Constructor)
Blob
Branch
BufferPtr
basicDBExceptionReporter
beginTrans
beginTransaction
1 (Function)
2 (Function)
bindBlob
bindByPos
bindDouble
bindInt
bindInt64
bindNull
bindOutputByPos
bindP
bindRun
bindString
bindType
bindValFormat
bindValOid
bindValPtr
bindValSize
addfile ./doc/html/doc-index-C.html hunk ./doc/html/doc-index-C.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (C)
CAconnect_timeout
CAdbname
CAhost
CAhostaddr
CAoptions
CApassword
CAport
CAservice
CAsslmode
CAuser
CaughtMonadIO
ColNum
ColumnInfo
ColumnResultBuffer
Command
ConnHandle
ConnParm
1 (Type/Class)
2 (Data Constructor)
ConnStatusType
ConnStruct
1 (Type/Class)
2 (Data Constructor)
ConnectA
1 (Type/Class)
2 (Data Constructor)
ConnectAttr
Context
1 (Type/Class)
2 (Data Constructor)
ContextPtr
cStr
1 (Function)
2 (Function)
3 (Function)
cStrLen
1 (Function)
2 (Function)
3 (Function)
catchDB
catchDBError
catchOCI
catchPG
catchSqlite
check'stmt
closeDb
1 (Function)
2 (Function)
colVal
colValBlob
colValDouble
1 (Function)
2 (Function)
colValFloat
colValInt
1 (Function)
2 (Function)
colValInt64
1 (Function)
2 (Function)
colValNull
colValPtr
colValString
1 (Function)
2 (Function)
commit
1 (Function)
2 (Function)
commitTrans
connect
1 (Function)
2 (Function)
3 (Function)
4 (Function)
currentRowNum
cursorCurrent
cursorIsEOF
cursorNext
addfile ./doc/html/doc-index-D.html hunk ./doc/html/doc-index-D.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (D)
DBBind
DBError
DBException
DBFatal
DBHandle
1 (Type/Class)
2 (Type/Class)
DBHandleStruct
1 (Type/Class)
2 (Type/Class)
3 (Data Constructor)
DBLiteralValue
DBM
DBNoData
DBType
DBUnexpectedNull
DefnHandle
DefnStruct
1 (Type/Class)
2 (Data Constructor)
Don'tRunTests
dateOracle
datePG
dateSqlite
dbLogoff
dbLogon
dbname
defineByPos
destroyQuery
destroyStmt
disconnect
doQuery
addfile ./doc/html/doc-index-E.html hunk ./doc/html/doc-index-E.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (E)
EnvHandle
EnvStruct
1 (Type/Class)
2 (Data Constructor)
ErrorHandle
ErrorStruct
1 (Type/Class)
2 (Data Constructor)
ExecStatusType
envCreate
errorTest
execCommand
execDDL
execDML
execPrepared
execPreparedCommand
executeCommand
expectBindInt
expectBindIntDoubleString
expectFloatsAndInts
expectPolymorphicFetchNull
expectRebind1
expectRebind2
addfile ./doc/html/doc-index-F.html hunk ./doc/html/doc-index-F.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (F)
Format
FreeFunPtr
fPQclear
fPQcmdStatus
fPQcmdTuples
fPQconnectdb
fPQdb
fPQerrorMessage
fPQexecParams
fPQexecPrepared
fPQfformat
fPQfinish
fPQfname
fPQftype
fPQgetisnull
fPQgetlength
fPQgetvalue
fPQnfields
fPQntuples
fPQoidValue
fPQprepare
fPQreset
fPQresultErrorMessage
fPQresultStatus
fPQsetErrorVerbosity
fPQsetNoticeProcessor
fPQsetNoticeReceiver
fPQstatus
fetchCol
fetchOneRow
formatDBException
formatEnvMsg
formatErrorCodeDesc
formatErrorMsg
formatMsgCommon
formatOCIMsg
freeBuffer
fromCChar
fromCDouble
fromCFloat
fromCInt
fromCInt16
fromCInt32
fromCInt64
fromEnumOCIErrorCode
fromUTF8
fromUTF8E
fromUTF8WE
addfile ./doc/html/doc-index-G.html hunk ./doc/html/doc-index-G.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (G)
gbracket
gcatch
gcatchJust
getAndRaiseError
getError
1 (Function)
2 (Function)
getHandleAttr
getOCIErrorMsg
getOCIErrorMsg2
getParam
getSession
gfinally
gtry
gtryJust
addfile ./doc/html/doc-index-H.html hunk ./doc/html/doc-index-H.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (H)
handleAlloc
handleFree
addfile ./doc/html/doc-index-I.html hunk ./doc/html/doc-index-I.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (I)
IPrepared
IQuery
ISession
IsolationLevel
IterAct
IterResult
ifNull
ignoreDBError
iterBindDate
iterBindInt
iterBindIntDoubleString
iterBindString
iterBoundaryDates
iterCursor
iterDate
iterEmptyString
iterNullDate
iterNullString
iterPolymorphicFetch
iterPolymorphicFetchNull
iterUnhandledNull
addfile ./doc/html/doc-index-L.html hunk ./doc/html/doc-index-L.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (L)
Leaf
literalDate
literalDouble
literalFloat
literalInt
literalInt64
addfile ./doc/html/doc-index-M.html hunk ./doc/html/doc-index-M.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (M)
MyTree
main
1 (Function)
2 (Function)
makeCalTime
makeQuery
mkCInt
mkCShort
mkNoticeProcessor
mkNoticeReceiver
mkOCICallbackInBind
mkOCICallbackOutBind
addfile ./doc/html/doc-index-N.html hunk ./doc/html/doc-index-N.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (N)
NextResultSet
1 (Type/Class)
2 (Data Constructor)
NoticeProcessor
NoticeReceiver
newBinaryValue
newUTF8String
nqExec
addfile ./doc/html/doc-index-O.html hunk ./doc/html/doc-index-O.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (O)
OCIBuffer
1 (Type/Class)
2 (Data Constructor)
OCICallbackInBind
OCICallbackOutBind
OCIException
1 (Type/Class)
2 (Data Constructor)
OCIHandle
OCIStruct
1 (Type/Class)
2 (Data Constructor)
Oid
OracleFunctions
1 (Type/Class)
2 (Data Constructor)
ociAttrGet
ociAttrSet
ociBindByPos
ociBindDynamic
ociDefineByPos
ociEnvCreate
ociErrorGet
ociHandleAlloc
ociHandleFree
ociLogoff
ociLogon
ociParamGet
ociServerAttach
ociServerDetach
ociSessionBegin
ociSessionEnd
ociStmtExecute
ociStmtFetch
ociStmtPrepare
ociTerminate
ociTransCommit
ociTransRollback
ociTransStart
oci_CRED_EXT
oci_CRED_PROXY
oci_CRED_RDBMS
oci_DEFAULT
oci_FETCH_ABSOLUTE
oci_FETCH_FIRST
oci_FETCH_LAST
oci_FETCH_NEXT
oci_FETCH_PRIOR
oci_FETCH_RELATIVE
oci_FETCH_RESERVED
oci_NTV_SYNTAX
oci_SQLT_AFC
oci_SQLT_AVC
oci_SQLT_BIN
oci_SQLT_CHR
oci_SQLT_DAT
oci_SQLT_FLT
oci_SQLT_INT
oci_SQLT_LBI
oci_SQLT_LNG
oci_SQLT_LVB
oci_SQLT_LVC
oci_SQLT_NUM
oci_SQLT_RID
oci_SQLT_RSET
oci_SQLT_STR
oci_SQLT_UIN
oci_SQLT_VBI
oci_SQLT_VCS
oci_SQLT_VNU
oci_TRANS_READONLY
oci_TRANS_READWRITE
oci_TRANS_SERIALIZABLE
openDb
1 (Function)
2 (Function)
addfile ./doc/html/doc-index-P.html hunk ./doc/html/doc-index-P.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (P)
PGBindVal
1 (Type/Class)
2 (Data Constructor)
PGException
1 (Type/Class)
2 (Data Constructor)
PGSqlFunctions
1 (Type/Class)
2 (Data Constructor)
PGType
PGVerbosity
PGconn
PGresult
ParamHandle
ParamLen
ParamStruct
1 (Type/Class)
2 (Data Constructor)
Position
PreparationA
1 (Type/Class)
2 (Data Constructor)
PreparedStmt
1 (Type/Class)
2 (Data Constructor)
peekUTF8String
peekValueRev
pgNewValue
pgPeek
pgSize
pgTypeFormat
pgTypeOid
prefetch
1 (Function)
2 (Function)
3 (Function)
prefetchRowCount
prepare'n'exec
preparePrefetch
prepareStmt
1 (Function)
2 (Function)
3 (Function)
print_
pswd
addfile ./doc/html/doc-index-Q.html hunk ./doc/html/doc-index-Q.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (Q)
QueryResourceUsage
1 (Type/Class)
2 (Data Constructor)
addfile ./doc/html/doc-index-R.html hunk ./doc/html/doc-index-R.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (R)
ReadCommitted
ReadUncommitted
RefCursor
1 (Type/Class)
2 (Data Constructor)
RepeatableRead
ResultSetHandle
RowNum
RunTests
reportResults
reportRethrow
result
result'
rethrowPG
reverseBytes
reverseBytes'
rollback
1 (Function)
2 (Function)
rollbackTrans
rowCounter
runSingleTest
runTest
1 (Function)
2 (Function)
3 (Function)
4 (Function)
5 (Function)
6 (Function)
7 (Function)
8 (Function)
runTestTT
addfile ./doc/html/doc-index-S.html hunk ./doc/html/doc-index-S.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (S)
Serialisable
Serializable
ServerHandle
ServerStruct
1 (Type/Class)
2 (Data Constructor)
SessHandle
SessStruct
1 (Type/Class)
2 (Data Constructor)
Session
1 (Type/Class)
2 (Type/Class)
3 (Type/Class)
4 (Type/Class)
ShouldRunTests
SqlState
SqlStateClass
SqlStateSubClass
SqliteCallback
SqliteException
1 (Type/Class)
2 (Data Constructor)
SqliteFunctions
1 (Type/Class)
2 (Data Constructor)
Statement
StmtHandle
1 (Type/Class)
2 (Type/Class)
StmtStruct
1 (Type/Class)
2 (Data Constructor)
3 (Type/Class)
4 (Type/Class)
5 (Data Constructor)
sbph
1 (Function)
2 (Function)
serverAttach
serverDetach
sessionBegin
sessionEnd
setHandleAttr
setHandleAttrString
sql
1 (Function)
2 (Function)
3 (Function)
4 (Function)
sqlRows2Power17
sqlRows2Power20
sql_tuned
sqlbind
1 (Function)
2 (Function)
3 (Function)
sqliteBindBlob
sqliteBindDouble
sqliteBindInt
sqliteBindInt64
sqliteBindNull
sqliteBindText
sqliteBindText16
sqliteChanges
sqliteClose
sqliteColumnBlob
sqliteColumnBytes
sqliteColumnDouble
sqliteColumnInt
sqliteColumnInt64
sqliteColumnText
sqliteColumnText16
sqliteDONE
sqliteERROR
sqliteErrcode
sqliteErrmsg
sqliteExec
sqliteFinalise
sqliteFree
sqliteOK
sqliteOpen
sqlitePrepare
sqliteROW
sqliteReset
sqliteStep
stmtChanges
stmtExec
1 (Function)
2 (Function)
stmtExec0
stmtExecImm
stmtExecute
stmtFetch
1 (Function)
2 (Function)
stmtFinalise
1 (Function)
2 (Function)
stmtPrepare
1 (Function)
2 (Function)
3 (Function)
stmtReset
addfile ./doc/html/doc-index-T.html hunk ./doc/html/doc-index-T.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (T)
TestException
TestFailure
TestResult
TestSuccess
terminate
testForError
1 (Function)
2 (Function)
testForErrorWithPtr
1 (Function)
2 (Function)
throwDB
throwIfDBNull
throwOCI
throwPG
throwSqlite
throwUserError
toCChar
toCDouble
toCFloat
toCInt
toCInt16
toCInt32
toCInt64
toUTF8
addfile ./doc/html/doc-index-U.html hunk ./doc/html/doc-index-U.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (U)
UTF16CString
UTF8CString
UserHandle
UserStruct
1 (Type/Class)
2 (Data Constructor)
user
addfile ./doc/html/doc-index-V.html hunk ./doc/html/doc-index-V.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (V)
Void
addfile ./doc/html/doc-index-W.html hunk ./doc/html/doc-index-W.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (W)
withBoundStatement
withCursor
withPreparedStatement
withSession
withTransaction
withUTF8String
withUTF8StringLen
addfile ./doc/html/doc-index-Z.html hunk ./doc/html/doc-index-Z.html 1 + + + (Index)
 ContentsIndex
ABCDEFGHILMNOPQRSTUVWZ
Index (Z)
zeroPad
addfile ./doc/html/doc-index.html hunk ./doc/html/doc-index.html 1 + + + (Index)
 ContentsIndex
Index
ABCDEFGHILMNOPQRSTUVWZ
addfile ./doc/html/haddock.css hunk ./doc/html/haddock.css 1 +/* -------- Global things --------- */ + +BODY { + background-color: #ffffff; + color: #000000; + font-family: sans-serif; + } + +A:link { color: #0000e0; text-decoration: none } +A:visited { color: #0000a0; text-decoration: none } +A:hover { background-color: #e0e0ff; text-decoration: none } + +TABLE.vanilla { + width: 100%; + border-width: 0px; + /* I can't seem to specify cellspacing or cellpadding properly using CSS... */ +} + +TABLE.vanilla2 { + border-width: 0px; +} + +/* font is a little too small in MSIE */ +TT { font-size: 100%; } +PRE { font-size: 100%; } + +LI P { margin: 0pt } + +TD { + border-width: 0px; +} + +TABLE.narrow { + border-width: 0px; +} + +TD.s8 { height: 8px; } +TD.s15 { height: 15px; } + +SPAN.keyword { text-decoration: underline; } + +/* Resize the buttom image to match the text size */ +IMG.coll { width : 0.75em; height: 0.75em; margin-bottom: 0; margin-right: 0.5em } + +/* --------- Contents page ---------- */ + +DIV.node { + padding-left: 3em; +} + +DIV.cnode { + padding-left: 1.75em; +} + +SPAN.pkg { + position: absolute; + left: 50em; +} + +/* --------- Documentation elements ---------- */ + +TD.children { + padding-left: 25px; + } + +TD.synopsis { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace + } + +TD.decl { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace; + vertical-align: top; + } + +/* + arg is just like decl, except that wrapping is not allowed. It is + used for function and constructor arguments which have a text box + to the right, where if wrapping is allowed the text box squashes up + the declaration by wrapping it. +*/ +TD.arg { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace; + vertical-align: top; + white-space: nowrap; + } + +TD.recfield { padding-left: 20px } + +TD.doc { + padding-top: 2px; + padding-left: 10px; + } + +TD.ndoc { + padding: 2px; + } + +TD.rdoc { + padding: 2px; + padding-left: 10px; + width: 100%; + } + +TD.body { + padding-left: 10px + } + +TD.pkg { + width: 100%; + padding-left: 10px +} + +TD.indexentry { + vertical-align: top; + padding-right: 10px + } + +TD.indexannot { + vertical-align: top; + padding-left: 20px; + white-space: nowrap + } + +TD.indexlinks { + width: 100% + } + +/* ------- Section Headings ------- */ + +TD.section1 { + padding-top: 15px; + font-weight: bold; + font-size: 150% + } + +TD.section2 { + padding-top: 10px; + font-weight: bold; + font-size: 130% + } + +TD.section3 { + padding-top: 5px; + font-weight: bold; + font-size: 110% + } + +TD.section4 { + font-weight: bold; + font-size: 100% + } + +/* -------------- The title bar at the top of the page */ + +TD.infohead { + color: #ffffff; + font-weight: bold; + padding-right: 10px; + text-align: left; +} + +TD.infoval { + color: #ffffff; + padding-right: 10px; + text-align: left; +} + +TD.topbar { + background-color: #000099; + padding: 5px; +} + +TD.title { + color: #ffffff; + padding-left: 10px; + width: 100% + } + +TD.topbut { + padding-left: 5px; + padding-right: 5px; + border-left-width: 1px; + border-left-color: #ffffff; + border-left-style: solid; + white-space: nowrap; + } + +TD.topbut A:link { + color: #ffffff + } + +TD.topbut A:visited { + color: #ffff00 + } + +TD.topbut A:hover { + background-color: #6060ff; + } + +TD.topbut:hover { + background-color: #6060ff + } + +TD.modulebar { + background-color: #0077dd; + padding: 5px; + border-top-width: 1px; + border-top-color: #ffffff; + border-top-style: solid; + } + +/* --------- The page footer --------- */ + +TD.botbar { + background-color: #000099; + color: #ffffff; + padding: 5px + } +TD.botbar A:link { + color: #ffffff; + text-decoration: underline + } +TD.botbar A:visited { + color: #ffff00 + } +TD.botbar A:hover { + background-color: #6060ff + } + addfile ./doc/html/haddock.js hunk ./doc/html/haddock.js 1 +// Haddock JavaScript utilities +function toggle(button,id) +{ + var n = document.getElementById(id).style; + if (n.display == "none") + { + button.src = "minus.gif"; + n.display = "block"; + } + else + { + button.src = "plus.gif"; + n.display = "none"; + } +} addfile ./doc/html/haskell_icon.gif binary ./doc/html/haskell_icon.gif oldhex * newhex *47494638376110001000f70f00000000800000008000808000000080800080008080c0c0c08080 *80ff000000ff00ffff000000ffff00ff00ffffffffff0000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *0021f90401000000002c000000001000100007086c0001007840b0a0418202073e38b0b021c387 *07143e2440c0a143040e091cd0787021c686151f84347800e343901d4b12646870e44a930d0952 *3ca832a6cc990555b2bc2992e4c79d3847ea2c88b3a7c89a2c8b8aa43874e941a60810003840b5 *aa55aa511346ddca75abc080003b addfile ./doc/html/index.html hunk ./doc/html/index.html 1 + + +
 ContentsIndex
Modules
show/hideControl
show/hideException
Control.Exception.MonadIO
show/hideDatabase
Database.Enumerator
Database.InternalEnumerator
show/hideOracle
Database.Oracle.Enumerator
Database.Oracle.OCIConstants
Database.Oracle.OCIFunctions
show/hideTest
Database.Oracle.Test.Enumerator
Database.Oracle.Test.OCIFunctions
show/hidePostgreSQL
Database.PostgreSQL.Enumerator
Database.PostgreSQL.PGFunctions
show/hideTest
Database.PostgreSQL.Test.Enumerator
Database.PostgreSQL.Test.PGFunctions
show/hideSqlite
Database.Sqlite.Enumerator
Database.Sqlite.SqliteFunctions
show/hideTest
Database.Sqlite.Test.Enumerator
Database.Sqlite.Test.SqliteFunctions
show/hideStub
Database.Stub.Enumerator
show/hideTest
Database.Stub.Test.Enumerator
show/hideTest
Database.Test.Enumerator
Database.Test.MultiConnect
Database.Test.Performance
show/hideForeign
show/hideC
Foreign.C.Unicode
Main
show/hideTest
Test.MiniUnit
Test.MiniUnitTest
Produced by Haddock version 0.7
addfile ./doc/html/minus.gif binary ./doc/html/minus.gif oldhex * newhex *47494638396109000900910000fefefe8282820202020000002c00000000090009000002118c8f *a00bc6eb5e0b40583b6596f1a11f14003b addfile ./doc/html/plus.gif binary ./doc/html/plus.gif oldhex * newhex *47494638396109000900910000fefefe8282820202020000002c00000000090009000002148c8f *a00bb6b29c82ca897b5b7871cfce74085200003b }