haskelldb-0.12: SQL unwrapper for Haskell.Source codeContentsIndex
Database.HaskellDB.Database
Portabilitynon-portable
Stabilityexperimental
Maintainerhaskelldb-users@lists.sourceforge.net
Contents
Operators
Type declarations
Function declarations
Description
Defines standard database operations and the primitive hooks that a particular database binding must provide.
Synopsis
(!.) :: Select f r a => r -> f -> a
data Database = Database {
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 ()
}
class GetRec er vr | er -> vr, vr -> er where
getRec :: GetInstances s -> Rel er -> Scheme -> s -> IO (Record vr)
data GetInstances s = GetInstances {
getString :: s -> String -> IO (Maybe String)
getInt :: s -> String -> IO (Maybe Int)
getInteger :: s -> String -> IO (Maybe Integer)
getDouble :: s -> String -> IO (Maybe Double)
getBool :: s -> String -> IO (Maybe Bool)
getCalendarTime :: s -> String -> IO (Maybe CalendarTime)
}
query :: GetRec er vr => Database -> Query (Rel er) -> IO [Record vr]
insert :: (ToPrimExprs r, ShowRecRow r, InsertRec r er) => Database -> Table er -> Record r -> IO ()
delete :: ShowRecRow r => Database -> Table r -> (Rel r -> Expr Bool) -> IO ()
update :: (ShowLabels s, ToPrimExprs s) => Database -> Table r -> (Rel r -> Expr Bool) -> (Rel r -> Record s) -> IO ()
insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO ()
tables :: Database -> IO [TableName]
describe :: Database -> TableName -> IO [(Attribute, FieldDesc)]
transaction :: Database -> IO a -> IO a
createDB :: Database -> String -> IO ()
createTable :: Database -> TableName -> [(Attribute, FieldDesc)] -> IO ()
dropDB :: Database -> String -> IO ()
dropTable :: Database -> TableName -> IO ()
Operators
(!.) :: Select f r a => r -> f -> aSource
The (!.) operator selects over returned records from the database (= rows) Non-overloaded version of !. For backwards compatibility.
Type declarations
data Database Source
Constructors
Database
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 ()
class GetRec er vr | er -> vr, vr -> er whereSource
Methods
getRecSource
::
=> GetInstances sPhantom argument to the the return type right
-> Rel erFields to get.
-> SchemeDriver-specific result data (for example a Statement object)
-> sResult record.
-> IO (Record vr)
Create a result record.
show/hide 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
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.
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
deleteSource
:: ShowRecRow r
=> DatabaseThe table to delete records from
-> Table rPredicate used to select records to delete
-> Rel r -> Expr Bool
-> IO ()
deletes a bunch of records
updateSource
:: (ShowLabels s, ToPrimExprs s)
=> DatabaseThe table to update
-> Table rPredicate used to select records to update
-> Rel r -> Expr BoolFunction used to modify selected records
-> Rel r -> Record s
-> IO ()
Updates records
insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO ()Source
Inserts values from a query into a table
tablesSource
:: DatabaseDatabase
-> IO [TableName]Names of all tables in the database
List all tables in the database
describeSource
:: DatabaseDatabase
-> TableNameName 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
transactionSource
::
=> DatabaseAction to run
-> IO a
-> IO a
Performs some database action in a transaction. If no exception is thrown, the changes are committed.
createDBSource
:: DatabaseDatabase
-> StringName 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
createTableSource
:: DatabaseDatabase
-> TableNameName of table to create
-> [(Attribute, FieldDesc)]The fields of the table
-> IO ()
dropDBSource
:: DatabaseDatabase
-> StringName of database to drop
-> IO ()
dropTableSource
:: DatabaseDatabase
-> TableNameName of table to drop
-> IO ()
Produced by Haddock version 2.6.0