haskey-0.3.1.0: A transactional, 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

data ConcurrentDb root Source #

An active concurrent database.

This can be shared amongst threads.

Open, close and create databases

data ConcurrentHandles Source #

All necessary database handles.

Instances
Show ConcurrentHandles Source # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Monad

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

Defined in Database.Haskey.Alloc.Concurrent.Internal.Monad

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 # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Monad

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 # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Monad

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.

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.

Instances
(Key k, Value v) => Root (Tree k v) Source # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Meta

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).

Instances
Show root => Show (ConcurrentMeta root) Source # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Meta

Generic (ConcurrentMeta root) Source # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Meta

Associated Types

type Rep (ConcurrentMeta root) :: Type -> Type #

Methods

from :: ConcurrentMeta root -> Rep (ConcurrentMeta root) x #

to :: Rep (ConcurrentMeta root) x -> ConcurrentMeta root #

Binary root => Binary (ConcurrentMeta root) Source # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Meta

Methods

put :: ConcurrentMeta root -> Put #

get :: Get (ConcurrentMeta root) #

putList :: [ConcurrentMeta root] -> Put #

type Rep (ConcurrentMeta root) Source # 
Instance details

Defined in Database.Haskey.Alloc.Concurrent.Internal.Meta

type Rep (ConcurrentMeta root) = D1 (MetaData "ConcurrentMeta" "Database.Haskey.Alloc.Concurrent.Internal.Meta" "haskey-0.3.1.0-HwnqosrjtX4FBQhqq0zmUK" False) (C1 (MetaCons "ConcurrentMeta" PrefixI True) (((S1 (MetaSel (Just "concurrentMetaRevision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TxId) :*: S1 (MetaSel (Just "concurrentMetaDataNumPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeData PageId))) :*: (S1 (MetaSel (Just "concurrentMetaIndexNumPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeIndex PageId)) :*: S1 (MetaSel (Just "concurrentMetaRoot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 root))) :*: ((S1 (MetaSel (Just "concurrentMetaDataFreeTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeData FreeTree)) :*: S1 (MetaSel (Just "concurrentMetaIndexFreeTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeIndex FreeTree))) :*: (S1 (MetaSel (Just "concurrentMetaOverflowTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OverflowTree) :*: (S1 (MetaSel (Just "concurrentMetaDataCachedFreePages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeData [FreePage])) :*: S1 (MetaSel (Just "concurrentMetaIndexCachedFreePages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (S TypeIndex [FreePage])))))))

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.

Methods

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.