Safe Haskell | None |
---|---|
Language | Haskell98 |
DSL/interpreter model for a generic key-value database
- class (Ord (Key t), Show (Key t), Show (Entry t), Typeable t, Show t, Pretty t, Pretty (Key t), Pretty (Entry t)) => Table t where
- data DatabaseF t next
- = Describe t (Doc -> next)
- | FetchList t [Key t] (Either SomeException (Map (Key t) (Entry t)) -> next)
- | FetchAll t (Either SomeException (Map (Key t) (Entry t)) -> next)
- | Update t (Key t) (Entry t -> Entry t) (Either SomeException () -> next)
- | InsertList t [(Key t, Entry t)] (Either SomeException () -> next)
- | DeleteList t [Key t] (Either SomeException () -> next)
- | Purge t (Either SomeException () -> next)
- | Commit t (Either SomeException () -> next)
- data CoDatabaseF t m a = CoDatabaseF {
- describeH :: m (Doc, a)
- fetchListH :: [Key t] -> m (Either SomeException (Map (Key t) (Entry t)), a)
- fetchAllH :: m (Either SomeException (Map (Key t) (Entry t)), a)
- updateH :: Key t -> (Entry t -> Entry t) -> m (Either SomeException (), a)
- insertListH :: [(Key t, Entry t)] -> m (Either SomeException (), a)
- deleteListH :: [Key t] -> m (Either SomeException (), a)
- purgeH :: m (Either SomeException (), a)
- commitH :: m (Either SomeException (), a)
- 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
- describeDatabase :: (MonadFree f m, DatabaseF t :<: f) => t -> m Doc
- fetch :: (MonadFree f m, DatabaseF t :<: f, Table t, MonadThrow m) => t -> Key t -> m (Entry t)
- fetchList :: (MonadFree f m, DatabaseF t :<: f, MonadThrow m) => t -> [Key t] -> m (Map (Key t) (Entry t))
- fetchAll :: (MonadThrow m, MonadFree f m, DatabaseF t :<: f) => t -> m (Map (Key t) (Entry t))
- update :: (MonadFree f m, DatabaseF t :<: f, MonadThrow m) => t -> Key t -> (Entry t -> Entry t) -> m ()
- insert :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> Key t -> Entry t -> m ()
- insertList :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> [(Key t, Entry t)] -> m ()
- delete :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> Key t -> m ()
- deleteList :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> [Key t] -> m ()
- purge :: (MonadThrow m, MonadFree f m, DatabaseF t :<: f, LoggerF :<: f) => t -> m ()
- commit :: (MonadThrow m, MonadFree f m, DatabaseF t :<: f, LoggerF :<: f) => t -> m ()
DSL/interpreter
class (Ord (Key t), Show (Key t), Show (Entry t), Typeable t, Show t, Pretty t, Pretty (Key t), Pretty (Entry t)) => Table t Source #
Generic database table
data DatabaseF t next Source #
Database DSL
Describe t (Doc -> next) | |
FetchList t [Key t] (Either SomeException (Map (Key t) (Entry t)) -> next) | |
FetchAll t (Either SomeException (Map (Key t) (Entry t)) -> next) | |
Update t (Key t) (Entry t -> Entry t) (Either SomeException () -> next) | |
InsertList t [(Key t, Entry t)] (Either SomeException () -> next) | |
DeleteList t [Key t] (Either SomeException () -> next) | |
Purge t (Either SomeException () -> next) | |
Commit t (Either SomeException () -> next) |
data CoDatabaseF t m a Source #
Database interpreter
CoDatabaseF | |
|
Exception
data DatabaseException t Source #
NotCommitted t | |
NotDeleted t [Key t] | |
NotFound t [Key t] | |
NotInserted t [(Key t, Entry t)] | |
NotPurged t | |
NotUpdated t (Key t) | |
UnableFetchAll t |
(Eq t, Eq (Key t), Eq (Entry t)) => Eq (DatabaseException t) Source # | |
(Show t, Show (Key t), Show (Entry t)) => Show (DatabaseException t) Source # | |
(Pretty t, Pretty (Key t)) => Pretty (DatabaseException t) Source # | |
(Table t, Show (Key t), Show (Entry t), Pretty (Key t), Typeable * t) => Exception (DatabaseException t) Source # | |
Primitives
fetch :: (MonadFree f m, DatabaseF t :<: f, Table t, MonadThrow m) => t -> Key t -> m (Entry t) Source #
fetchList :: (MonadFree f m, DatabaseF t :<: f, MonadThrow m) => t -> [Key t] -> m (Map (Key t) (Entry t)) Source #
fetchAll :: (MonadThrow m, MonadFree f m, DatabaseF t :<: f) => t -> m (Map (Key t) (Entry t)) Source #
update :: (MonadFree f m, DatabaseF t :<: f, MonadThrow m) => t -> Key t -> (Entry t -> Entry t) -> m () Source #
insert :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> Key t -> Entry t -> m () Source #
insertList :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> [(Key t, Entry t)] -> m () Source #
delete :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> Key t -> m () Source #
deleteList :: (MonadThrow m, MonadFree f m, LoggerF :<: f, DatabaseF t :<: f) => t -> [Key t] -> m () Source #