|
Database.InternalEnumerator | Portability | non-portable | Stability | experimental | Maintainer | oleg@pobox.com, alistair@abayley.org |
|
|
|
|
|
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 |
|
|
|
|
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 () |
| | 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 | |
|
|
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 |
| | Instances | |
|
|
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 |
| | 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 () |
| | Instances | |
|
|
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 | This is really just a wrapper that lets us write lists of
heterogenous bind values e.g. [bindP string, bindP (0::Int), ...]
|
| | Instances | |
|
|
data IsolationLevel |
Constructors | ReadUncommitted | | ReadCommitted | | RepeatableRead | | Serialisable | | Serializable | for alternative spellers
|
| 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 () |
| | Instances | |
|
|
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 |
| | Instances | |
|
|
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 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 | |
|
|
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 |