Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | haskelldb-users@lists.sourceforge.net |
Safe Haskell | None |
Database.HaskellDB.Database
Description
Defines standard database operations and the primitive hooks that a particular database binding must provide.
- (!.) :: 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 ()
- dbCommit :: IO ()
- class GetRec er vr | er -> vr, vr -> er where
- 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)
- getLocalTime :: s -> String -> IO (Maybe LocalTime)
- class GetValue a where
- getValue :: GetInstances s -> s -> String -> IO a
- 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
- commit :: Database -> IO ()
- 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
Constructors
Database | |
Fields
|
class GetRec er vr | er -> vr, vr -> er whereSource
Methods
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.
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
|
Methods
getValue :: GetInstances s -> s -> String -> IO aSource
Instances
GetValue Bool | |
GetValue Double | |
GetValue Int | |
GetValue Integer | |
GetValue String | |
GetValue CalendarTime | |
GetValue LocalTime | |
GetValue (Maybe Bool) | |
GetValue (Maybe Double) | |
GetValue (Maybe Int) | |
GetValue (Maybe Integer) | |
GetValue (Maybe String) | |
GetValue (Maybe CalendarTime) | |
GetValue (Maybe LocalTime) | |
Size n => GetValue (Maybe (BoundedString n)) | |
Size n => GetValue (BoundedString n) |
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
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
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
List all tables in the database
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
Performs some database action in a transaction. If no exception is thrown, the changes are committed.
Is not very useful. You need to be root to use it. We suggest you solve this in another way