| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
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. This isn't so valuable now, because it's dead easy to install SQLite, but it's still there if you want to try it. Additional reading:
Note that there are a few functions that are exported from each DBMS-specific implementation which are exposed to the API user, and which are part of the Takusen API, but are not (necessarily) in this module. They include:
These functions will typically have the same names and intentions, but their specific types and usage may differ between DBMS. | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Synopsis | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
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 (sql "create table blah") execDML (sql "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 (sql "update blah ...") execDML (sql "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 [] liftIO $ putStrLn $ show r otherActions session Notes:
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:
sql "select ..."
prefetch 100 "select ..." [bindP ..., bindP ...]
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 function 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 Parameters 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, returning the wrapped accumulator/seed value. 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 value. 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 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, UTCTime. (Int64 is often, but not always, supported.) By directly support we mean there is type-specific marshalling code implemented. 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)] ) reduces to (by using IterAct and IterResult): 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 iteratee 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:
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 DBMS's. 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, which also exists in the Oracle and SQLite interfaces). 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 bstmt iter [] liftIO (print actual) Note that we pass bstmt to doQuery; this is the bound statement object created by withBoundStatement. 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 bstmt 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 the Sqlite implementation 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. 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 | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Support for returning multiple result sets from a single statement exists for PostgreSQL and Oracle. Such functionality does not exist in SQLite. 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: If 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:
Nested style: The linear style of cursor processing is the only style supported by MS SQL Server and ODBC (which we do not yet support). However, PostgreSQL and Oracle also support using nested cursors in queries. Again for PostgreSQL, 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: 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. For Oracle the example is slightly different. The reason it's different is that Oracle requires two things:
Contrast this with the PostgreSQL example, where the entire result-set is processed to give a list of RefCursor values, and then we run a list of actions over this list with mapM_. This is possible because PostgreSQL refcursors are just the database cursor names, which are Strings, which we can marshal to Haskell values easily. selectNestedMultiResultSet = do let q = "select n, cursor(SELECT nat2.n, cursor" ++ " (SELECT nat3.n from t_natural nat3 where nat3.n < nat2.n order by n)" ++ " from t_natural nat2 where nat2.n < nat.n order by n)" ++ " from t_natural nat where n < 10 order by n" iterMain (outer::Int) (c::RefCursor StmtHandle) acc = do rs <- doQuery c (iterInner outer) [] result' ((outer,c):acc) iterInner outer (inner::Int) (c::RefCursor StmtHandle) acc = do rs <- doQuery c (iterInner2 outer inner) [] result' ((inner,c):acc) iterInner2 outer inner (i::Int) acc = do liftIO (putStrLn (show outer ++ " " ++ show inner ++ " " ++ show i)) result' (i:acc) withTransaction RepeatableRead $ do rs <- doQuery (sql q) iterMain [] return () Note that the PostgreSQL example can also be written like this (except, of course, that the actual query text is that from the PostgreSQL exanple). | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Sessions and Transactions | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
data 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 | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
execDDL :: Command stmt s => stmt -> DBM mark s () | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
DDL operations don't manipulate data, so we return no information. If there is a problem, an exception will be raised. | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
execDML :: Command stmt s => stmt -> DBM mark s Int | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Returns the number of rows affected. | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Exceptions and handlers | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
data DBException | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
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 | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
withPreparedStatement | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
withBoundStatement | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
bindP :: DBBind a sess stmt bo => a -> BindA sess stmt bo | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
This is really just a wrapper that lets us write lists of heterogenous bind values e.g. [bindP string, bindP (0::Int), ...] | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Iteratees and Cursors | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
doQuery | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
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 | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
data RefCursor a | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
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:
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 | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Utilities | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
ifNull | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
| ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
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). | ||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Produced by Haddock version 0.7 |