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

Safe HaskellNone
LanguageHaskell2010

Database.Haskey.Store.Class

Contents

Description

A storage back-end manages physical storage of pages.

Synopsis

Class

class (Applicative m, Monad m) => StoreM hnd m | m -> hnd where Source #

A storage back-end that can store and fetch physical pages.

Methods

openHandle :: hnd -> m () Source #

Open a database handle for reading and writing.

lockHandle :: hnd -> m () Source #

Obtain a lock on the given handle, so no other process can access it.

releaseHandle :: hnd -> m () Source #

Release the lock on the given handle, so other processes can access it.

flushHandle :: hnd -> m () Source #

Flush the contents of a handle to disk (or other storage).

closeHandle :: hnd -> m () Source #

Close a database handle.

removeHandle :: hnd -> m () Source #

Remove a handle from the storage back-end.

nodePageSize :: (Key key, Value val) => m (Height height -> Node height key val -> PageSize) Source #

A function that calculates the hypothetical size of a node, if it were to be written to a page (regardless of the maximum page size).

maxPageSize :: m PageSize Source #

The maximum page size the allocator can handle.

maxKeySize :: m Word64 Source #

Get the maximum key size

The default implementation will repeatedly call calculateMaxKeySize. You might want to cache this value in your own implementation.

maxValueSize :: m Word64 Source #

Get the maximum value size

The default implementation will repeatedly call calculateMaxValueSize. You might want to cache this value in your own implementation.

getNodePage :: (Key key, Value val) => hnd -> Height height -> Proxy key -> Proxy val -> NodeId height key val -> m (Node height key val) Source #

Read a page and return the actual node and the transaction id when the node was written.

putNodePage :: (Key key, Value val) => hnd -> Height height -> NodeId height key val -> Node height key val -> m () Source #

Write a node to a physical page.

getOverflow :: Value val => hnd -> Proxy val -> m val Source #

Read a value from an overflow page

putOverflow :: Value val => hnd -> val -> m () Source #

Write a value to an overflow page

listOverflows :: hnd -> m [hnd] Source #

List overflow pages in the specific overflow directory.

The result should include **AT LEAST** the handles in the specified directory, but it may contain more handles, even handles that do not belong to an overflow page.

Instances
StoreM hnd m => StoreM hnd (StateT s m) Source # 
Instance details

Defined in Database.Haskey.Store.Class

Methods

openHandle :: hnd -> StateT s m () Source #

lockHandle :: hnd -> StateT s m () Source #

releaseHandle :: hnd -> StateT s m () Source #

flushHandle :: hnd -> StateT s m () Source #

closeHandle :: hnd -> StateT s m () Source #

removeHandle :: hnd -> StateT s m () Source #

nodePageSize :: (Key key, Value val) => StateT s m (Height height -> Node height key val -> PageSize) Source #

maxPageSize :: StateT s m PageSize Source #

maxKeySize :: StateT s m Word64 Source #

maxValueSize :: StateT s m Word64 Source #

getNodePage :: (Key key, Value val) => hnd -> Height height -> Proxy key -> Proxy val -> NodeId height key val -> StateT s m (Node height key val) Source #

putNodePage :: (Key key, Value val) => hnd -> Height height -> NodeId height key val -> Node height key val -> StateT s m () Source #

getOverflow :: Value val => hnd -> Proxy val -> StateT s m val Source #

putOverflow :: Value val => hnd -> val -> StateT s m () Source #

listOverflows :: hnd -> StateT s m [hnd] Source #

(Applicative m, Monad m, MonadIO m, MonadThrow m, Ord fp, Show fp, Typeable fp) => StoreM fp (MemoryStoreT fp m) Source # 
Instance details

Defined in Database.Haskey.Store.InMemory

Methods

openHandle :: fp -> MemoryStoreT fp m () Source #

lockHandle :: fp -> MemoryStoreT fp m () Source #

releaseHandle :: fp -> MemoryStoreT fp m () Source #

flushHandle :: fp -> MemoryStoreT fp m () Source #

closeHandle :: fp -> MemoryStoreT fp m () Source #

removeHandle :: fp -> MemoryStoreT fp m () Source #

nodePageSize :: (Key key, Value val) => MemoryStoreT fp m (Height height -> Node height key val -> PageSize) Source #

maxPageSize :: MemoryStoreT fp m PageSize Source #

maxKeySize :: MemoryStoreT fp m Word64 Source #

maxValueSize :: MemoryStoreT fp m Word64 Source #

getNodePage :: (Key key, Value val) => fp -> Height height -> Proxy key -> Proxy val -> NodeId height key val -> MemoryStoreT fp m (Node height key val) Source #

putNodePage :: (Key key, Value val) => fp -> Height height -> NodeId height key val -> Node height key val -> MemoryStoreT fp m () Source #

getOverflow :: Value val => fp -> Proxy val -> MemoryStoreT fp m val Source #

putOverflow :: Value val => fp -> val -> MemoryStoreT fp m () Source #

listOverflows :: fp -> MemoryStoreT fp m [fp] Source #

(Applicative m, Monad m, MonadIO m, MonadThrow m) => StoreM FilePath (FileStoreT FilePath m) Source # 
Instance details

Defined in Database.Haskey.Store.File

StoreM hnd m => StoreM hnd (ReaderT s m) Source # 
Instance details

Defined in Database.Haskey.Store.Class

Methods

openHandle :: hnd -> ReaderT s m () Source #

lockHandle :: hnd -> ReaderT s m () Source #

releaseHandle :: hnd -> ReaderT s m () Source #

flushHandle :: hnd -> ReaderT s m () Source #

closeHandle :: hnd -> ReaderT s m () Source #

removeHandle :: hnd -> ReaderT s m () Source #

nodePageSize :: (Key key, Value val) => ReaderT s m (Height height -> Node height key val -> PageSize) Source #

maxPageSize :: ReaderT s m PageSize Source #

maxKeySize :: ReaderT s m Word64 Source #

maxValueSize :: ReaderT s m Word64 Source #

getNodePage :: (Key key, Value val) => hnd -> Height height -> Proxy key -> Proxy val -> NodeId height key val -> ReaderT s m (Node height key val) Source #

putNodePage :: (Key key, Value val) => hnd -> Height height -> NodeId height key val -> Node height key val -> ReaderT s m () Source #

getOverflow :: Value val => hnd -> Proxy val -> ReaderT s m val Source #

putOverflow :: Value val => hnd -> val -> ReaderT s m () Source #

listOverflows :: hnd -> ReaderT s m [hnd] Source #

Helpers

arbitrarySearch :: (Ord v, Integral n) => n -> (n -> v) -> v -> n Source #

Search an arbitrary number, less than a limit, greater than a starting value.

calculateMaxKeySize Source #

Arguments

:: PageSize

Maximum pages size

-> (Node Z ZeroEncoded ZeroEncoded -> PageSize)

Function that calculates the page size of a node

-> Word64

Maximum key size

Calculate the maximum key size.

Return the size for which at least 4 key-value pairs with keys and values of that size can fit in a leaf node.

calculateMaxValueSize Source #

Arguments

:: PageSize

Maximum page size

-> Word64

Maximum key size

-> (Node Z ZeroEncoded ZeroEncoded -> PageSize)

Function that calculates the page size of a node

-> Word64

Maximum value size

Calculate the maximum value size.

Return the size for which at least 4 key-value pairs of the specified maximum key size and values of the returned size can fit in a leaf node. that size can fit in a leaf node.