haskey-0.1.0.1: A transcatoinal, ACID compliant, embeddable key-value store.

Safe HaskellNone
LanguageHaskell2010

Database.Haskey.Alloc.Concurrent

Contents

Description

The module implements an page allocator with page reuse and support for multiple readers and serialized writers.

Synopsis

Allocator

Open, close and create databases

data ConcurrentHandles Source #

All necessary database handles.

Instances

Show ConcurrentHandles Source # 
ConcurrentMetaStoreM m => AllocReaderM (ConcurrentT WriterEnv ConcurrentHandles m) Source # 

Methods

readNode :: (Key key, Value val) => Height height -> NodeId height key val -> ConcurrentT WriterEnv ConcurrentHandles m (Node height key val) #

readOverflow :: Value val => OverflowId -> ConcurrentT WriterEnv ConcurrentHandles m val #

ConcurrentMetaStoreM m => AllocReaderM (ConcurrentT ReaderEnv ConcurrentHandles m) Source # 

Methods

readNode :: (Key key, Value val) => Height height -> NodeId height key val -> ConcurrentT ReaderEnv ConcurrentHandles m (Node height key val) #

readOverflow :: Value val => OverflowId -> ConcurrentT ReaderEnv ConcurrentHandles m val #

(ConcurrentMetaStoreM m, MonadIO m) => AllocM (ConcurrentT WriterEnv ConcurrentHandles m) Source # 

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.

Instances

(Show k, Show v) => Show (ConcurrentMeta k v) Source # 
Generic (ConcurrentMeta k v) Source # 

Associated Types

type Rep (ConcurrentMeta k v) :: * -> * #

Methods

from :: ConcurrentMeta k v -> Rep (ConcurrentMeta k v) x #

to :: Rep (ConcurrentMeta k v) x -> ConcurrentMeta k v #

(Binary k, Binary v) => Binary (ConcurrentMeta k v) Source # 

Methods

put :: ConcurrentMeta k v -> Put #

get :: Get (ConcurrentMeta k v) #

putList :: [ConcurrentMeta k v] -> Put #

type Rep (ConcurrentMeta k v) Source # 
type Rep (ConcurrentMeta k v) = D1 (MetaData "ConcurrentMeta" "Database.Haskey.Alloc.Concurrent.Meta" "haskey-0.1.0.1-GzE5NfiBJHFJQHWUYXDJlg" False) (C1 (MetaCons "ConcurrentMeta" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "concurrentMetaRevision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TxId)) (S1 (MetaSel (Just Symbol "concurrentMetaDataNumPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeData PageId)))) ((:*:) (S1 (MetaSel (Just Symbol "concurrentMetaIndexNumPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeIndex PageId))) (S1 (MetaSel (Just Symbol "concurrentMetaTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Tree k v))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "concurrentMetaDataFreeTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeData FreeTree))) (S1 (MetaSel (Just Symbol "concurrentMetaIndexFreeTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeIndex FreeTree)))) ((:*:) (S1 (MetaSel (Just Symbol "concurrentMetaOverflowTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OverflowTree)) ((:*:) (S1 (MetaSel (Just Symbol "concurrentMetaDataFreshUnusedPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeData (Set DirtyFree)))) (S1 (MetaSel (Just Symbol "concurrentMetaIndexFreshUnusedPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeIndex (Set DirtyFree)))))))))

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.

Minimal complete definition

putConcurrentMeta, readConcurrentMeta

Methods

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.