|
|
|
|
|
|
| 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 | | | | | 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 | | | | | 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 :: DBBind a sess stmt bo => a -> BindA sess stmt bo | | | class ISession sess => IQuery q sess b | q -> sess, q -> b where | | | | 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
|
|
|
Instances | |
|
|
|
| Instances | |
|
|
|
Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | ReadUncommitted | | | ReadCommitted | | | RepeatableRead | | | Serialisable | | | Serializable | for alternative spellers
|
| Instances | |
|
|
|
|
|
|
|
|
| Exceptions and handlers
|
|
|
| Constructors | | DBError SqlState Int String | DBMS error message.
| | DBFatal SqlState Int String | | | DBUnexpectedNull RowNum ColNum | 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.
| | DBNoData | Thrown by cursor functions if you try to fetch after the end.
|
| Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Preparing and Binding
|
|
| data PreparedStmt mark stmt | Source |
|
|
|
| :: (Typeable a, IPrepared stmt sess bstmt bo) | | | => PreparationA sess stmt | preparation action to create prepared statement;
this action is usually created by prepareQuery/Command
| | -> PreparedStmt mark stmt -> DBM mark sess a | DBM action that takes a prepared statement
| | -> DBM mark sess a | |
|
|
|
| :: (Typeable a, IPrepared stmt s bstmt bo) | | | => PreparedStmt mark stmt | prepared 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 | |
|
|
|
| Instances | |
|
|
|
| Instances | |
|
|
| class ISession sess => EnvInquiry inquirykey sess result | inquirykey sess -> result | Source |
|
|
|
| data PreparationA sess stmt | Source |
|
|
| class ISession sess => IPrepared stmt sess bound_stmt bo | stmt -> bound_stmt, stmt -> bo | Source |
|
|
|
| data BindA sess stmt bo | Source |
|
|
|
|
|
|
| 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 where | Source |
|
| | Methods | | | Instances | |
|
|
|
| :: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) | | | => stmt | query
| | -> i | iteratee function
| | -> seed | seed value
| | -> DBM mark sess seed | |
|
|
| class DBType a q b | q -> b | Source |
|
| Instances | |
|
|
|
|
|
|
|
|
| data NextResultSet mark stmt | Source |
|
|
|
|
|
|
|
|
| cursorCurrent :: DBCursor mark (DBM mark s) a -> DBM mark s a | Source |
|
|
| cursorNext :: DBCursor mark (DBM mark s) a -> DBM mark s (DBCursor mark (DBM mark s) a) | Source |
|
|
|
| :: (Typeable a, Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) | | | => stmt | query
| | -> i | iteratee function
| | -> seed | seed value
| | -> DBCursor mark (DBM mark sess) seed -> DBM mark sess a | action taking cursor parameter
| | -> DBM mark sess a | |
|
|
|
|
| Utilities
|
|
|
| :: | | | => Maybe a | nullable value
| | -> a | value to substitute if first parameter is null i.e. Data.Maybe.Nothing
| | -> a | |
|
|
|
|
|
|
| Produced by Haddock version 2.1.0 |