-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC. -- -- Takusen is a DBMS access library. Like HSQL and HDBC, we support -- arbitrary SQL statements (currently strings, extensible to anything -- that can be converted to a string). -- -- Takusen's unique selling point is safety and efficiency. We statically -- ensure all acquired database resources - such as cursors, connections, -- and statement handles - are released, exactly once, at predictable -- times. Takusen can avoid loading the whole result set in memory, and -- so can handle queries returning millions of rows in constant space. -- Takusen also supports automatic marshalling and unmarshalling of -- results and query parameters. These benefits come from the design of -- query result processing around a left-fold enumerator. -- -- Currently we fully support ODBC, Oracle, Sqlite, and PostgreSQL. @package Takusen @version 0.8.6 -- | Marshall Haskell Strings to and from UTF8-encoded CStrings. This -- module's code is inspired by John Meacham's UTF8 en- & de-coders, -- and also those found in the HXT library (module -- Text.XML.HXT.DOM.Unicode). -- -- Note that the -Len functions all return the length in bytes, not Chars -- (this is more useful, as you are most likely to want to pass the -- length to an FFI function, which is most likely expecting the length -- in bytes). If you want the length in Chars, well, you have the -- original String, so... module Foreign.C.UTF8 -- | Analogous to peekCString. Converts UTF8 CString to String. peekUTF8String :: CString -> IO String -- | Analogous to peekCStringLen. Converts UTF8 CString to String. The -- resulting String will end either when len bytes have been -- converted, or when a NULL is found. peekUTF8StringLen :: CStringLen -> IO String -- | Analogous to newCString. Creates UTF8 encoded CString. newUTF8String :: String -> IO CString -- | Analogous to withCString. Creates UTF8 encoded CString. withUTF8String :: String -> (CString -> IO a) -> IO a -- | Analogous to withCStringLen. The length returned is in bytes (encoding -- units), not chars. withUTF8StringLen :: String -> (CStringLen -> IO a) -> IO a -- | Convert a Haskell String into a UTF8 String, where each UTF8 byte is -- represented by its Char equivalent i.e. only chars 0-255 are used. The -- resulting String can be marshalled to CString directly i.e. with a -- Latin-1 encoding. toUTF8String :: String -> String -- | Convert a String that was marshalled from a CString without any -- decoder applied. This might be useful if the client encoding is -- unknown, and the user code must convert. We assume that the UTF8 -- CString was marshalled as if Latin-1 i.e. all chars are in the range -- 0-255. fromUTF8String :: String -> String lengthUTF8 :: String -> Int -- | Convert UTF-8 to Unicode. fromUTF8 :: [Word8] -> String -- | Convert Unicode characters to UTF-8. toUTF8 :: String -> [Word8] -- | Utility functions. Mostly used in database back-ends, and tests. module Database.Util class Show a => MyShow a show_ :: MyShow a => a -> String -- | Like System.IO.print, except that Strings are not escaped or -- quoted. print_ :: (MonadIO m, MyShow a) => a -> m () -- | Convenience for making UTCTimes. Assumes the time given is already UTC -- time i.e. there's no timezone adjustment. mkUTCTime :: (Integral a, Real b) => a -> a -> a -> a -> a -> b -> UTCTime mkCalTime :: Integral a => a -> a -> a -> a -> a -> a -> CalendarTime int64ToDateParts :: Int64 -> (Int64, Int64, Int64, Int64, Int64, Int64) datePartsToInt64 :: (Integral a1, Integral a2, Integral a3, Integral a4, Integral a5, Integral a6) => (a1, a2, a3, a4, a5, a6) -> Int64 calTimeToInt64 :: CalendarTime -> Int64 int64ToCalTime :: Int64 -> CalendarTime int64ToUTCTime :: Int64 -> UTCTime wordsBy :: (Char -> Bool) -> String -> [String] skipNonMatch :: (Char -> Bool) -> String -> [String] positions :: Eq a => [a] -> [a] -> [Int] pgDatetimetoUTCTime :: String -> UTCTime pgDatetimetoCalTime :: String -> CalendarTime pgDatetimeToParts :: String -> (Int, Int, Int, Int, Int, Double, Int) utcTimeToIsoString :: (Integral a, Integral b) => UTCTime -> String -> (a -> a) -> (b -> String) -> String utcTimeToPGDatetime :: UTCTime -> String utcTimeToIsoDatetime :: UTCTime -> String utcTimeToOdbcDatetime :: UTCTime -> String -- | Assumes CalendarTime is also UTC i.e. ignores ctTZ component. calTimeToPGDatetime :: CalendarTime -> String printArrayContents :: Int -> Ptr Word8 -> IO () instance [overlap ok] Show a => MyShow a instance [overlap ok] MyShow String module Control.Exception.MonadIO class MonadIO m => CaughtMonadIO m gcatch :: (CaughtMonadIO m, Exception e) => m a -> (e -> m a) -> m a gcatchJust :: (CaughtMonadIO m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a gtry :: (Exception e, CaughtMonadIO m) => m b -> m (Either e b) gtryJust :: (Exception e, CaughtMonadIO m) => (e -> 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 instance CaughtMonadIO m => CaughtMonadIO (ReaderT a m) instance CaughtMonadIO IO -- | 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. module Database.Enumerator data ISession sess => DBM mark sess a -- | The ISession class describes a database session to a particular -- DBMS. Oracle has its own Session object, SQLite has its own session -- object (which maintains the connection handle to the database engine -- and other related stuff). Session objects for different databases -- normally have different types -- yet they all belong to the class -- ISession so we can do generic operations like commit, -- execDDL, etc. in a database-independent manner. -- -- Session objects per se are created by database connection/login -- functions. -- -- The class ISession is thus an interface between low-level (and -- database-specific) code and the Enumerator, database-independent code. -- The ISession class is NOT visible to the end user -- neither -- the class, nor any of its methods. -- -- The ISession class describes the mapping from connection object -- to the session object. The connection object is created by the end -- user (and this is how the end user tells which particular back end he -- wants). The session object is not accessible by the end user in any -- way. Even the type of the session object should be hidden! class ISession 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 -- Database.Enumerator.Sqlite.connect function is to pass it out -- directly to Database.Enumerator.withSession. data ConnectA sess -- | Typeable constraint is to prevent the leakage of Session and other -- marked objects. withSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark. DBM mark sess a) -> IO a -- | Persistent database connections. This issue has been brought up by -- Shanky Surana. The following design is inspired by that exchange. -- -- On one hand, implementing persistent connections is easy. One may say -- we should have added them long time ago, to match HSQL, HDBC, and -- similar database interfaces. Alas, implementing persistent connection -- safely is another matter. The simplest design is like the following -- --
--   withContinuedSession :: (Typeable a, IE.ISession sess) => 
--       IE.ConnectA sess -> (forall mark. DBM mark sess a) -> 
--       IO (a, IE.ConnectA sess)
--   withContinuedSession (IE.ConnectA connecta) m = do
--       conn <- connecta
--       r <- runReaderT (unDBM m) conn
--       return (r,(return conn))
--   
-- -- so that the connection object is returned as the result and can be -- used again with withContinuedSession or withSession. The problem is -- that nothing prevents us from writing: -- --
--   (r1,conn) <- withContinuedSession (connect "...") query1
--   r2        <- withSession conn query2
--   r3        <- withSession conn query3
--   
-- -- That is, we store the suspended connection and then use it twice. But -- the first withSession closes the connection. So, the second -- withSession gets an invalid session object. Invalid in a sense that -- even memory may be deallocated, so there is no telling what happens -- next. Also, as we can see, it is difficult to handle errors and -- automatically dispose of the connections if the fatal error is -- encountered. -- -- All these problems are present in other interfaces... In the case of a -- suspended connection, the problem is how to enforce the linear -- access to a variable. It can be enforced, via a state-changing monad. -- The implementation below makes the non-linear use of a suspended -- connection a run-time checkable condition. It will be generic and safe -- - fatal errors close the connection, an attempt to use a closed -- connection raises an error, and we cannot reuse a connection. We have -- to write: -- --
--   (r1, conn1) <- withContinuedSession conn  ...
--   (r2, conn2) <- withContinuedSession conn1 ...
--   (r3, conn3) <- withContinuedSession conn2 ...
--   
-- -- etc. If we reuse a suspended connection or use a closed connection, we -- get a run-time (exception). That is of course not very satisfactory - -- and yet better than a segmentation fault. withContinuedSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark. DBM mark sess a) -> IO (a, ConnectA sess) commit :: ISession s => DBM mark s () rollback :: ISession s => DBM mark s () beginTransaction :: (MonadReader s (ReaderT s IO), ISession s) => IsolationLevel -> DBM mark s () -- | Perform an action as a transaction: commit afterwards, unless there -- was an exception, in which case rollback. withTransaction :: ISession s => IsolationLevel -> DBM mark s a -> DBM mark s a data IsolationLevel ReadUncommitted :: IsolationLevel ReadCommitted :: IsolationLevel RepeatableRead :: IsolationLevel Serialisable :: IsolationLevel -- | for alternative spellers Serializable :: IsolationLevel -- | DDL operations don't manipulate data, so we return no information. If -- there is a problem, an exception will be raised. execDDL :: Command stmt s => stmt -> DBM mark s () -- | Returns the number of rows affected. execDML :: Command stmt s => stmt -> DBM mark s Int -- | Allows arbitrary actions to be run the DBM monad. The back-end -- developer must supply instances of EnvInquiry, which is hidden away in -- Database.InternalEnumerator. An example of this is -- Database.Sqlite.Enumerator.LastInsertRowid. inquire :: EnvInquiry key s result => key -> DBM mark s result data DBException -- | DBMS error message. DBError :: SqlState -> Int -> String -> DBException DBFatal :: SqlState -> Int -> String -> DBException -- | the 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. DBUnexpectedNull :: RowNum -> ColNum -> DBException -- | Thrown by cursor functions if you try to fetch after the end. DBNoData :: DBException -- | A show for Database.InteralEnumerator.DBExceptions. formatDBException :: DBException -> String -- | This simple handler reports the error to stdout and swallows -- it i.e. it doesn't propagate. basicDBExceptionReporter :: CaughtMonadIO m => DBException -> m () -- | This handler reports the error and propagates it (usually to force the -- program to halt). reportRethrow :: CaughtMonadIO m => DBException -> m a -- | Same as reportRethrow, but you can prefix some text to the error -- (perhaps to indicate which part of your program raised it). reportRethrowMsg :: CaughtMonadIO m => String -> DBException -> m a -- | Catch Database.InteralEnumerator.DBExceptions thrown in the -- DBM monad. catchDB :: CaughtMonadIO m => m a -> (DBException -> m a) -> m a -- | If you want to trap a specific error number, use this. It passes -- anything else up. catchDBError :: CaughtMonadIO m => Int -> m a -> (DBException -> m a) -> m a -- | Analogous to catchDBError, but ignores specific errors instead -- (propagates anything else). ignoreDBError :: CaughtMonadIO m => Int -> m a -> m a -- | Throw a DBException. It's just a type-specific -- Control.Exception.throwDyn. throwDB :: DBException -> a type ColNum = Int type RowNum = Int type SqlState = (SqlStateClass, SqlStateSubClass) type SqlStateClass = String type SqlStateSubClass = String data PreparedStmt mark stmt -- | 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. withPreparedStatement :: (Typeable a, IPrepared stmt sess bstmt bo) => PreparationA sess stmt -> (PreparedStmt mark stmt -> DBM mark sess a) -> DBM mark sess 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 -- Database.InternalEnumerator.Statement, so it can be passed to -- doQuery in order to process the result-set, and also an -- instance of Database.InternalEnumerator.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. withBoundStatement :: (Typeable a, IPrepared stmt s bstmt bo) => PreparedStmt mark stmt -> [BindA s stmt bo] -> (bstmt -> DBM mark s a) -> DBM mark s a -- | Statement defines the API for query objects i.e. which types -- can be queries. class ISession sess => Statement stmt sess q | stmt sess -> q -- | 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). class ISession sess => Command stmt sess class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> result -- | 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. data PreparationA sess stmt class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, 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). data BindA sess stmt bo -- | 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. class ISession sess => DBBind a sess stmt bo | stmt -> bo bindP :: DBBind a sess stmt bo => a -> BindA sess stmt bo -- | 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. class ISession sess => IQuery q sess b | q -> sess, q -> b currentRowNum :: IQuery q sess b => q -> IO Int -- | The left-fold interface. doQuery :: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) => stmt -> i -> seed -> DBM mark sess seed -- | 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. class DBType a q b | q -> b -- | IterResult and IterAct give us some type sugar. Without -- them, the types of iteratee functions become quite unwieldy. type IterResult seedType = Either seedType seedType type IterAct m seedType = seedType -> m (IterResult seedType) data NextResultSet mark stmt NextResultSet :: (PreparedStmt mark stmt) -> NextResultSet mark stmt data RefCursor a RefCursor :: a -> RefCursor a -- | 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
--   
cursorIsEOF :: DBCursor mark (DBM mark s) a -> DBM mark s Bool -- | Returns the results fetched so far, processed by iteratee function. cursorCurrent :: DBCursor mark (DBM mark s) a -> DBM mark s a -- | Advance the cursor. Returns the cursor. The return value is usually -- ignored. cursorNext :: DBCursor mark (DBM mark s) a -> DBM mark s (DBCursor mark (DBM mark s) 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. 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 type Position = Int -- | Useful utility function, for SQL weenies. ifNull :: Maybe a -> a -> 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). result' :: Monad m => IterAct m a instance [overlap ok] Functor (DBM mark sess) instance [overlap ok] Monad (DBM mark sess) instance [overlap ok] MonadIO (DBM mark sess) instance [overlap ok] MonadFix (DBM mark sess) instance [overlap ok] MonadReader sess (DBM mark sess) instance [overlap ok] (QueryIteratee m q i' seed b, DBType a q b) => QueryIteratee m q (a -> i') seed b instance [overlap ok] (DBType a q b, MonadIO m) => QueryIteratee m q (a -> seed -> m (IterResult seed)) seed b instance [overlap ok] ISession si => CaughtMonadIO (DBM mark si)