| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Imm.Database
Contents
Description
Database module abstracts over a key-value database that supports CRUD operations.
- class (Ord (Key t), Show (Key t), Show (Entry t), Typeable t, Show t, Pretty t, Pretty (Key t)) => Table t where
- class MonadThrow m => MonadDatabase t m where
- data DatabaseException t
- = NotCommitted t
- | NotDeleted t [Key t]
- | NotFound t [Key t]
- | NotInserted t [(Key t, Entry t)]
- | NotPurged t
- | NotUpdated t (Key t)
- | UnableFetchAll t
- fetch :: (MonadDatabase t m, Table t, MonadThrow m) => t -> Key t -> m (Entry t)
- fetchList :: (MonadDatabase t m, MonadThrow m) => t -> [Key t] -> m (Map (Key t) (Entry t))
- fetchAll :: (MonadThrow m, MonadDatabase t m) => t -> m (Map (Key t) (Entry t))
- update :: (MonadDatabase t m, MonadThrow m) => t -> Key t -> (Entry t -> Entry t) -> m ()
- insert :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> Key t -> Entry t -> m ()
- insertList :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> [(Key t, Entry t)] -> m ()
- delete :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> Key t -> m ()
- deleteList :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> [Key t] -> m ()
- purge :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> m ()
- commit :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> m ()
Types
class (Ord (Key t), Show (Key t), Show (Entry t), Typeable t, Show t, Pretty t, Pretty (Key t)) => Table t Source #
Generic database table
class MonadThrow m => MonadDatabase t m where Source #
Monad capable of interacting with a key-value store.
Minimal complete definition
_describeDatabase, _fetchList, _fetchAll, _update, _insertList, _deleteList, _purge, _commit
Methods
_describeDatabase :: t -> m (Doc a) Source #
_fetchList :: t -> [Key t] -> m (Map (Key t) (Entry t)) Source #
_fetchAll :: t -> m (Map (Key t) (Entry t)) Source #
_update :: t -> Key t -> (Entry t -> Entry t) -> m () Source #
_insertList :: t -> [(Key t, Entry t)] -> m () Source #
_deleteList :: t -> [Key t] -> m () Source #
data DatabaseException t Source #
Constructors
| NotCommitted t | |
| NotDeleted t [Key t] | |
| NotFound t [Key t] | |
| NotInserted t [(Key t, Entry t)] | |
| NotPurged t | |
| NotUpdated t (Key t) | |
| UnableFetchAll t |
Instances
| (Eq t, Eq (Key t), Eq (Entry t)) => Eq (DatabaseException t) Source # | |
| (Show t, Show (Key t), Show (Entry t)) => Show (DatabaseException t) Source # | |
| (Table t, Show (Key t), Show (Entry t), Pretty (Key t), Typeable * t) => Exception (DatabaseException t) Source # | |
| (Pretty t, Pretty (Key t)) => Pretty (DatabaseException t) Source # | |
Primitives
fetch :: (MonadDatabase t m, Table t, MonadThrow m) => t -> Key t -> m (Entry t) Source #
fetchList :: (MonadDatabase t m, MonadThrow m) => t -> [Key t] -> m (Map (Key t) (Entry t)) Source #
fetchAll :: (MonadThrow m, MonadDatabase t m) => t -> m (Map (Key t) (Entry t)) Source #
update :: (MonadDatabase t m, MonadThrow m) => t -> Key t -> (Entry t -> Entry t) -> m () Source #
insert :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> Key t -> Entry t -> m () Source #
insertList :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> [(Key t, Entry t)] -> m () Source #
delete :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> Key t -> m () Source #
deleteList :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> [Key t] -> m () Source #
purge :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> m () Source #
commit :: (MonadThrow m, MonadDatabase t m, MonadLog m) => t -> m () Source #