haskelldb-2.2.4: A library of combinators for generating and executing SQL statements.

CopyrightDaan Leijen (c) 1999, daan@cs.uu.nl HWT Group (c) 2003, haskelldb-users@lists.sourceforge.net
LicenseBSD-style
Maintainerhaskelldb-users@lists.sourceforge.net
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Database.HaskellDB.Database

Contents

Description

Defines standard database operations and the primitive hooks that a particular database binding must provide.

Synopsis

Operators

(!.) :: Select f r a => r -> f -> a infix 9 Source

The (!.) operator selects over returned records from the database (= rows) Non-overloaded version of !. For backwards compatibility.

Type declarations

data Database Source

Constructors

Database 

Fields

dbQuery :: forall er vr. GetRec er vr => PrimQuery -> Rel er -> IO [Record vr]
 
dbInsert :: TableName -> Assoc -> IO ()
 
dbInsertQuery :: TableName -> PrimQuery -> IO ()
 
dbDelete :: TableName -> [PrimExpr] -> IO ()
 
dbUpdate :: TableName -> [PrimExpr] -> Assoc -> IO ()
 
dbTables :: IO [TableName]
 
dbDescribe :: TableName -> IO [(Attribute, FieldDesc)]
 
dbTransaction :: forall a. IO a -> IO a
 
dbCreateDB :: String -> IO ()
 
dbCreateTable :: TableName -> [(Attribute, FieldDesc)] -> IO ()
 
dbDropDB :: String -> IO ()
 
dbDropTable :: TableName -> IO ()
 
dbCommit :: IO ()
 

class GetRec er vr | er -> vr, vr -> er where Source

Methods

getRec Source

Arguments

:: GetInstances s

Driver functions for getting values of different types.

-> Rel er

Phantom argument to the the return type right

-> Scheme

Fields to get.

-> s

Driver-specific result data (for example a Statement object)

-> IO (Record vr)

Result record.

Create a result record.

Instances

GetRec RecNil RecNil 
(GetValue a, GetRec er vr) => GetRec (RecCons f (Expr a) er) (RecCons f a vr) 

data GetInstances s Source

Functions for getting values of a given type. Database drivers need to implement these functions and pass this record to getRec when getting query results.

All these functions should return Nothing if the value is NULL.

Constructors

GetInstances 

Fields

getString :: s -> String -> IO (Maybe String)

Get a String value.

getInt :: s -> String -> IO (Maybe Int)

Get an Int value.

getInteger :: s -> String -> IO (Maybe Integer)

Get an Integer value.

getDouble :: s -> String -> IO (Maybe Double)

Get a Double value.

getBool :: s -> String -> IO (Maybe Bool)

Get a Bool value.

getCalendarTime :: s -> String -> IO (Maybe CalendarTime)

Get a CalendarTime value.

getLocalTime :: s -> String -> IO (Maybe LocalTime)

Get a LocalTime value.

Function declarations

query :: GetRec er vr => Database -> Query (Rel er) -> IO [Record vr] Source

performs a query on a database

insert :: (ToPrimExprs r, ShowRecRow r, InsertRec r er) => Database -> Table er -> Record r -> IO () Source

Inserts a record into a table

delete Source

Arguments

:: ShowRecRow r 
=> Database

The database

-> Table r

The table to delete records from

-> (Rel r -> Expr Bool)

Predicate used to select records to delete

-> IO () 

deletes a bunch of records

update Source

Arguments

:: (ShowLabels s, ToPrimExprs s) 
=> Database

The database

-> Table r

The table to update

-> (Rel r -> Expr Bool)

Predicate used to select records to update

-> (Rel r -> Record s)

Function used to modify selected records

-> IO () 

Updates records

insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO () Source

Inserts values from a query into a table

tables Source

Arguments

:: Database

Database

-> IO [TableName]

Names of all tables in the database

List all tables in the database

describe Source

Arguments

:: Database

Database

-> TableName

Name of the tables whose columns are to be listed

-> IO [(Attribute, FieldDesc)]

Name and type info for each column

List all columns in a table, along with their types

transaction Source

Arguments

:: Database

Database

-> IO a

Action to run

-> IO a 

Performs some database action in a transaction. If no exception is thrown, the changes are committed.

commit Source

Arguments

:: Database

Database

-> IO () 

Commit any pending data to the database.

createDB Source

Arguments

:: Database

Database

-> String

Name of database to create

-> IO () 

Is not very useful. You need to be root to use it. We suggest you solve this in another way

createTable Source

Arguments

:: Database

Database

-> TableName

Name of table to create

-> [(Attribute, FieldDesc)]

The fields of the table

-> IO () 

dropDB Source

Arguments

:: Database

Database

-> String

Name of database to drop

-> IO () 

dropTable Source

Arguments

:: Database

Database

-> TableName

Name of table to drop

-> IO ()