Safe Haskell | None |
---|---|
Language | Haskell2010 |
The module implements an page allocator with page reuse and support for multiple readers and serialized writers.
- data ConcurrentDb root = ConcurrentDb {}
- data ConcurrentHandles = ConcurrentHandles {}
- concurrentHandles :: FilePath -> ConcurrentHandles
- lockConcurrentDb :: ConcurrentMetaStoreM m => ConcurrentHandles -> m ()
- unlockConcurrentDb :: ConcurrentMetaStoreM m => ConcurrentHandles -> m ()
- createConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> root -> m (ConcurrentDb root)
- openConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (Maybe (ConcurrentDb root))
- closeConcurrentHandles :: (MonadIO m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m ()
- module Database.Haskey.Alloc.Transaction
- transact :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Root root) => (forall n. (AllocM n, MonadMask n) => root -> n (Transaction root a)) -> ConcurrentDb root -> m a
- transact_ :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Root root) => (forall n. (AllocM n, MonadMask n) => root -> n (Transaction root ())) -> ConcurrentDb root -> m ()
- transactReadOnly :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Root root) => (forall n. (AllocReaderM n, MonadMask n) => root -> n a) -> ConcurrentDb root -> m a
- class Value root => Root root
- data ConcurrentMeta root = ConcurrentMeta {
- concurrentMetaRevision :: TxId
- concurrentMetaDataNumPages :: S TypeData PageId
- concurrentMetaIndexNumPages :: S TypeIndex PageId
- concurrentMetaRoot :: root
- concurrentMetaDataFreeTree :: S TypeData FreeTree
- concurrentMetaIndexFreeTree :: S TypeIndex FreeTree
- concurrentMetaOverflowTree :: OverflowTree
- concurrentMetaDataCachedFreePages :: S TypeData [FreePage]
- concurrentMetaIndexCachedFreePages :: S TypeIndex [FreePage]
- class StoreM FilePath m => ConcurrentMetaStoreM m where
Allocator
data ConcurrentDb root Source #
An active concurrent database.
This can be shared amongst threads.
ConcurrentDb | |
|
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.
lockConcurrentDb :: ConcurrentMetaStoreM m => ConcurrentHandles -> m () Source #
Lock the database.
This needs to be called manually, if you want exclusive access, before
calling either createConcurrentDb
or openConcurrentDb
Use unlockConcurrentDb
using the bracket
pattern to properly unlock the
database.
unlockConcurrentDb :: ConcurrentMetaStoreM m => ConcurrentHandles -> m () Source #
Unlock the database.
createConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> root -> m (ConcurrentDb root) Source #
Open a new concurrent database, with the given handles.
openConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (Maybe (ConcurrentDb root)) 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, Root root) => (forall n. (AllocM n, MonadMask n) => root -> n (Transaction root a)) -> ConcurrentDb root -> m a Source #
Execute a write transaction, with a result.
transact_ :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Root root) => (forall n. (AllocM n, MonadMask n) => root -> n (Transaction root ())) -> ConcurrentDb root -> m () Source #
Execute a write transaction, without a result.
transactReadOnly :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Root root) => (forall n. (AllocReaderM n, MonadMask n) => root -> n a) -> ConcurrentDb root -> m a Source #
Execute a read-only transaction.
Storage requirements
class Value root => Root root Source #
User-defined data root stored inside ConcurrentMeta
.
This can be a user-defined collection of Tree
roots.
data ConcurrentMeta root Source #
Meta data of the page allocator.
The root
type parameter should be a user-defined collection of Tree
roots, instantiating the Root
type class.
To store store a single tree, use ConcurrentMeta (Tree k v)
.
Show root => Show (ConcurrentMeta root) Source # | |
Generic (ConcurrentMeta root) Source # | |
Binary root => Binary (ConcurrentMeta root) Source # | |
type Rep (ConcurrentMeta root) 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 :: Root root => FilePath -> ConcurrentMeta root -> m () Source #
Write the meta-data structure to a certain page.
readConcurrentMeta :: Root root => FilePath -> Proxy root -> m (Maybe (ConcurrentMeta root)) 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, MonadCatch m) => ConcurrentMetaStoreM (FileStoreT FilePath m) Source # | |
(Applicative m, Monad m, MonadIO m, MonadCatch m) => ConcurrentMetaStoreM (MemoryStoreT FilePath m) Source # | |