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

Safe HaskellNone
LanguageHaskell2010

Database.Haskey.Alloc.Concurrent.Meta

Description

This module implements data structures and function related to the metadata of the concurrent page allocator.

Synopsis

Documentation

data CurrentMetaPage Source #

Data type used to point to the most recent version of the meta data.

Constructors

Meta1 
Meta2 

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.0-Bj1GeZXJASRBI49cDY743O" 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.