haskey-0.1.0.0: A transcatoinal, 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

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

Open all concurrent handles.

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.

newConcurrentDb :: (Key k, Value v, MonadIO m) => ConcurrentHandles -> ConcurrentMeta k v -> m (ConcurrentDb k v) Source #

Create a new concurrent database with handles and metadata provided.

getCurrentMeta :: (Key k, Value v) => ConcurrentDb k v -> STM (ConcurrentMeta k v) Source #

Get the current meta data.

setCurrentMeta :: (MonadIO m, ConcurrentMetaStoreM m, Key k, Value v) => ConcurrentMeta k v -> ConcurrentDb k v -> m () Source #

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

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.

transactNow :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key k, Value v) => (forall n. (AllocM n, MonadMask n) => Tree k v -> n (Transaction k v a)) -> ConcurrentDb k v -> m a Source #

Execute a write transaction, without cleaning up old overflow pages.

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.

actAndCommit :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m, Key k, Value v) => ConcurrentDb k v -> (forall n. (MonadIO n, MonadMask n, ConcurrentMetaStoreM n) => ConcurrentMeta k v -> ConcurrentT WriterEnv ConcurrentHandles n (Maybe (ConcurrentMeta k v), 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 k v -> ConcurrentMeta k v Source #

Update the meta-data from a writer environment

saveOverflowIds :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => StateT (ConcurrentMeta k v, 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 k v, WriterEnv ConcurrentHandles) m () Source #

Save the free'd pages to the free page database

handleFreedDirtyPages :: (MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => StateT (ConcurrentMeta k v, WriterEnv ConcurrentHandles) m () Source #

Handle the dirty pages.

Save the newly created free dirty pages to the metadata for later use.

Update the database size.