Takusen-0.8.2: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.Source codeContentsIndex
Database.Enumerator
Contents
Usage
Iteratee Functions
result and result'
Rank-2 types, ($), and the monomorphism restriction
Bind Parameters
Multiple (and nested) Result Sets
Sessions and Transactions
Exceptions and handlers
Preparing and Binding
Iteratees and Cursors
Utilities
Synopsis
data ISession sess => DBM mark sess a
class ISession sess
data ConnectA sess
withSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark. DBM mark sess a) -> IO a
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 ()
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
inquire :: EnvInquiry key s result => key -> DBM mark s result
data DBException
= DBError SqlState Int String
| DBFatal SqlState Int String
| DBUnexpectedNull RowNum ColNum
| DBNoData
formatDBException :: DBException -> String
basicDBExceptionReporter :: CaughtMonadIO m => DBException -> m ()
reportRethrow :: CaughtMonadIO m => DBException -> m a
reportRethrowMsg :: CaughtMonadIO m => String -> DBException -> m a
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
type ColNum = Int
type RowNum = Int
type SqlState = (SqlStateClass, SqlStateSubClass)
type SqlStateClass = String
type SqlStateSubClass = String
data PreparedStmt mark 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
class ISession sess => Statement stmt sess q | stmt sess -> q
class ISession sess => Command stmt sess
class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> result
data PreparationA sess stmt
class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> bo
data BindA sess stmt bo
class ISession sess => DBBind a sess stmt bo | stmt -> bo where
bindP :: a -> BindA sess stmt bo
bindP :: DBBind a sess stmt bo => a -> BindA sess stmt bo
class ISession sess => IQuery q sess b | q -> sess, q -> b where
currentRowNum :: q -> IO Int
doQuery :: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) => stmt -> i -> seed -> DBM mark sess seed
class DBType a q b | q -> b
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
type Position = Int
ifNull :: Maybe a -> a -> a
result :: Monad m => IterAct m a
result' :: Monad m => IterAct m a
Usage
Iteratee Functions
result and result'
Rank-2 types, ($), and the monomorphism restriction
Bind Parameters
Multiple (and nested) Result Sets
Sessions and Transactions
data ISession sess => DBM mark sess a Source
show/hide Instances
MonadReader sess (DBM mark sess)
Monad (DBM mark sess)
Functor (DBM mark sess)
MonadFix (DBM mark sess)
MonadIO (DBM mark sess)
ISession si => CaughtMonadIO (DBM mark si)
class ISession sess Source
show/hide Instances
data ConnectA sess Source
show/hide Instances
withSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark. DBM mark sess a) -> IO aSource
withContinuedSession :: (Typeable a, ISession sess) => ConnectA sess -> (forall mark. DBM mark sess a) -> IO (a, ConnectA sess)Source
commit :: ISession s => DBM mark s ()Source
rollback :: ISession s => DBM mark s ()Source
beginTransaction :: (MonadReader s (ReaderT s IO), ISession s) => IsolationLevel -> DBM mark s ()Source
withTransaction :: ISession s => IsolationLevel -> DBM mark s a -> DBM mark s aSource
data IsolationLevel Source
Constructors
ReadUncommitted
ReadCommitted
RepeatableRead
Serialisable
Serializablefor alternative spellers
show/hide Instances
execDDL :: Command stmt s => stmt -> DBM mark s ()Source
execDML :: Command stmt s => stmt -> DBM mark s IntSource
inquire :: EnvInquiry key s result => key -> DBM mark s resultSource
Exceptions and handlers
data DBException Source
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
formatDBException :: DBException -> StringSource
basicDBExceptionReporter :: CaughtMonadIO m => DBException -> m ()Source
reportRethrow :: CaughtMonadIO m => DBException -> m aSource
reportRethrowMsg :: CaughtMonadIO m => String -> DBException -> m aSource
catchDB :: CaughtMonadIO m => m a -> (DBException -> m a) -> m aSource
catchDBError :: CaughtMonadIO m => Int -> m a -> (DBException -> m a) -> m aSource
ignoreDBError :: CaughtMonadIO m => Int -> m a -> m aSource
throwDB :: DBException -> aSource
type ColNum = IntSource
type RowNum = IntSource
type SqlState = (SqlStateClass, SqlStateSubClass)Source
type SqlStateClass = StringSource
type SqlStateSubClass = StringSource
Preparing and Binding
data PreparedStmt mark stmt Source
withPreparedStatementSource
:: (Typeable a, IPrepared stmt sess bstmt bo)
=> PreparationA sess stmtpreparation action to create prepared statement; this action is usually created by prepareQuery/Command
-> PreparedStmt mark stmt -> DBM mark sess aDBM action that takes a prepared statement
-> DBM mark sess a
withBoundStatementSource
:: (Typeable a, IPrepared stmt s bstmt bo)
=> PreparedStmt mark stmtprepared statement created by withPreparedStatement
-> [BindA s stmt bo]bind values
-> bstmt -> DBM mark s aaction to run over bound statement
-> DBM mark s a
class ISession sess => Statement stmt sess q | stmt sess -> qSource
show/hide Instances
Statement QueryStringTuned Session Query
Statement QueryString Session Query
class ISession sess => Command stmt sess Source
show/hide Instances
Command QueryStringTuned Session
Command QueryString Session
class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> resultSource
data PreparationA sess stmt Source
class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> boSource
data BindA sess stmt bo Source
class ISession sess => DBBind a sess stmt bo | stmt -> bo whereSource
Methods
bindP :: a -> BindA sess stmt boSource
bindP :: DBBind a sess stmt bo => a -> BindA sess stmt boSource
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
class ISession sess => IQuery q sess b | q -> sess, q -> b whereSource
Methods
currentRowNum :: q -> IO IntSource
show/hide Instances
IQuery Query Session ColumnBuffer
doQuerySource
:: (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
class DBType a q b | q -> bSource
show/hide Instances
DBType (Maybe Double) Query ColumnBuffer
DBType (Maybe Int) Query ColumnBuffer
DBType (Maybe String) Query ColumnBuffer
(Show a, Read a) => DBType (Maybe a) Query ColumnBuffer
DBType (Maybe CalendarTime) Query ColumnBuffer
type IterResult seedType = Either seedType seedTypeSource
type IterAct m seedType = seedType -> m (IterResult seedType)Source
currentRowNum :: IQuery q sess b => q -> IO IntSource
data NextResultSet mark stmt Source
Constructors
NextResultSet (PreparedStmt mark stmt)
data RefCursor a Source
Constructors
RefCursor a
cursorIsEOF :: DBCursor mark (DBM mark s) a -> DBM mark s BoolSource
cursorCurrent :: DBCursor mark (DBM mark s) a -> DBM mark s aSource
cursorNext :: DBCursor mark (DBM mark s) a -> DBM mark s (DBCursor mark (DBM mark s) a)Source
withCursorSource
:: (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 aaction taking cursor parameter
-> DBM mark sess a
type Position = IntSource
Utilities
ifNullSource
::
=> Maybe anullable value
-> avalue to substitute if first parameter is null i.e. Data.Maybe.Nothing
-> a
result :: Monad m => IterAct m aSource
result' :: Monad m => IterAct m aSource
Produced by Haddock version 2.1.0