Safe Haskell | None |
---|---|
Language | Haskell2010 |
The module implements an page allocator with page reuse and support for multiple readers and serialized writers.
- data ConcurrentDb k v = ConcurrentDb {}
- data ConcurrentHandles = ConcurrentHandles {}
- concurrentHandles :: FilePath -> ConcurrentHandles
- createConcurrentDb :: (Key k, Value v, MonadIO m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (ConcurrentDb k v)
- openConcurrentDb :: (Key k, Value v, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (Maybe (ConcurrentDb k v))
- closeConcurrentHandles :: (MonadIO m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m ()
- module Database.Haskey.Alloc.Transaction
- transact :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key key, Value val) => (forall n. (AllocM n, MonadMask n) => Tree key val -> n (Transaction key val a)) -> ConcurrentDb key val -> m a
- transact_ :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key k, Value v) => (forall n. (AllocM n, MonadMask n) => Tree k v -> n (Transaction k v ())) -> ConcurrentDb k v -> m ()
- transactReadOnly :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key key, Value val) => (forall n. (AllocReaderM n, MonadMask m) => Tree key val -> n a) -> ConcurrentDb key val -> m a
- data ConcurrentMeta k v = ConcurrentMeta {
- concurrentMetaRevision :: TxId
- concurrentMetaDataNumPages :: S TypeData PageId
- concurrentMetaIndexNumPages :: S TypeIndex PageId
- concurrentMetaTree :: Tree k v
- concurrentMetaDataFreeTree :: S TypeData FreeTree
- concurrentMetaIndexFreeTree :: S TypeIndex FreeTree
- concurrentMetaOverflowTree :: OverflowTree
- concurrentMetaDataFreshUnusedPages :: S TypeData (Set DirtyFree)
- concurrentMetaIndexFreshUnusedPages :: S TypeIndex (Set DirtyFree)
- class StoreM FilePath m => ConcurrentMetaStoreM m where
Allocator
data ConcurrentDb k v Source #
An active concurrent database.
This can be shared amongst threads.
Open, close and create databases
data ConcurrentHandles Source #
All necessary database handles.
concurrentHandles :: FilePath -> ConcurrentHandles Source #
Construct a set of ConcurrentHandles
from a root directory.
createConcurrentDb :: (Key k, Value v, MonadIO m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (ConcurrentDb k v) Source #
Open a new concurrent database, with the given handles.
openConcurrentDb :: (Key k, Value v, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (Maybe (ConcurrentDb k v)) Source #
Open the an existing database, with the given handles.
closeConcurrentHandles :: (MonadIO m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m () Source #
Close the handles of the database.
Manipulation and transactions
transact :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key key, Value val) => (forall n. (AllocM n, MonadMask n) => Tree key val -> n (Transaction key val a)) -> ConcurrentDb key val -> m a Source #
Execute a write transaction, with a result.
transact_ :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key k, Value v) => (forall n. (AllocM n, MonadMask n) => Tree k v -> n (Transaction k v ())) -> ConcurrentDb k v -> m () Source #
Execute a write transaction, without a result.
transactReadOnly :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key key, Value val) => (forall n. (AllocReaderM n, MonadMask m) => Tree key val -> n a) -> ConcurrentDb key val -> m a Source #
Execute a read-only transaction.
Storage requirements
data ConcurrentMeta k v Source #
Meta data of the page allocator.
(Show k, Show v) => Show (ConcurrentMeta k v) Source # | |
Generic (ConcurrentMeta k v) Source # | |
(Binary k, Binary v) => Binary (ConcurrentMeta k v) Source # | |
type Rep (ConcurrentMeta k v) Source # | |
class StoreM FilePath m => ConcurrentMetaStoreM m where Source #
A class representing the storage requirements of the page allocator.
A store supporting the page allocator should be an instance of this class.
putConcurrentMeta :: (Key k, Value v) => FilePath -> ConcurrentMeta k v -> m () Source #
Write the meta-data structure to a certain page.
readConcurrentMeta :: (Key k, Value v) => FilePath -> Proxy k -> Proxy v -> m (Maybe (ConcurrentMeta k v)) Source #
Try to read the meta-data structure from a handle, or return Nothing
if the handle doesn't contain a meta page.
(Applicative m, Monad m, MonadIO m, MonadThrow m) => ConcurrentMetaStoreM (FileStoreT FilePath m) Source # | |
(Applicative m, Monad m, MonadIO m, MonadThrow m) => ConcurrentMetaStoreM (MemoryStoreT FilePath m) Source # | |