haskey-0.2.0.0: A transactional, ACID compliant, embeddable key-value store.

Safe HaskellNone
LanguageHaskell2010

Database.Haskey.Alloc.Concurrent.Database

Description

This module implements data structures and functions related to the database.

Synopsis

Documentation

data ConcurrentDb root Source #

An active concurrent database.

This can be shared amongst threads.

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.

openConcurrentHandles :: ConcurrentMetaStoreM m => ConcurrentHandles -> m () Source #

Open all concurrent handles.

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.

newConcurrentDb :: (Root root, MonadIO m) => ConcurrentHandles -> ConcurrentMeta root -> m (ConcurrentDb root) Source #

Create a new concurrent database with handles and metadata provided.

getCurrentMeta :: Root root => ConcurrentDb root -> STM (ConcurrentMeta root) Source #

Get the current meta data.

setCurrentMeta :: (Root root, MonadIO m, ConcurrentMetaStoreM m) => ConcurrentMeta root -> ConcurrentDb root -> m () Source #

Write the new metadata, and switch the pointer to the current one.

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.

transactNow :: (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, without cleaning up old overflow pages.

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.

actAndCommit :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Root root) => ConcurrentDb root -> (forall n. (MonadIO n, MonadMask n, ConcurrentMetaStoreM n) => ConcurrentMeta root -> ConcurrentT WriterEnv ConcurrentHandles n (Maybe (ConcurrentMeta root), a)) -> m a Source #

Run a write action that takes the current meta-data and returns new meta-data to be commited, or Nothing if the write transaction should be aborted.

cleanupAfterException :: (MonadIO m, MonadCatch m, ConcurrentMetaStoreM m) => ConcurrentHandles -> TxId -> m () Source #

Cleanup after an exception occurs, or after a program crash.

The TxId of the aborted transaction should be passed.

removeNewlyAllocatedOverflows :: (MonadIO m, ConcurrentMetaStoreM m) => WriterEnv ConcurrentHandles -> m () Source #

Remove all overflow pages that were written in the transaction.

If the transaction is aborted, all written pages should be deleted.

updateMeta :: WriterEnv ConcurrentHandles -> ConcurrentMeta root -> ConcurrentMeta root Source #

Update the meta-data from a writer environment

saveOverflowIds :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => StateT (ConcurrentMeta root, WriterEnv ConcurrentHandles) m () Source #

Save the newly free'd overflow pages, for deletion on the next tx.

saveFreePages' :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => Int -> (forall a. a -> S t a) -> (forall hnds. WriterEnv hnds -> FileState t) -> (forall hnds. WriterEnv hnds -> FileState t -> WriterEnv hnds) -> StateT (ConcurrentMeta root, WriterEnv ConcurrentHandles) m () Source #

Save the free'd pages to the free page database

handleCachedFreePages :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => StateT (ConcurrentMeta root, WriterEnv ConcurrentHandles) m () Source #

Handle the cached free pages.

Save the cached free pages to the metadata for later use.

Update the database size.