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

Safe HaskellNone
LanguageHaskell2010

Database.Haskey.Store.InMemory

Contents

Description

Binary in-memory storage back-end. Can be used as a storage back-end for the append-only page allocator (see Data.BTree.Alloc).

Synopsis

Storage

data Page t where Source #

A decoded page, of a certain type t of kind PageType.

type MemoryFile = Map PageId ByteString Source #

A file containing a collection of pages.

type MemoryFiles fp = MVar (Map fp MemoryFile) Source #

A collection of Files, each associated with a certain fp handle.

This is shareable amongst multiple threads.

data MemoryStoreConfig Source #

Memory store configuration.

The default configuration can be obtained by using defMemoryStoreConfig.

A configuration with a specific page size can be obtained by using memoryStoreConfigWithPageSize.

defMemoryStoreConfig :: MemoryStoreConfig Source #

The default configuration.

This is an unwrapped memoryStoreConfigWithPageSize with a page size of 4096.

memoryStoreConfigWithPageSize :: PageSize -> Maybe MemoryStoreConfig Source #

Create a configuration with a specific page size.

The maximum key and value sizes are calculated using calculateMaxKeySize and calculateMaxValueSize.

If the page size is too small, Nothing is returned.

data MemoryStoreT fp m a Source #

Monad in which binary storage operations can take place.

Two important instances are StoreM making it a storage back-end, and ConcurrentMetaStoreM making it a storage back-end compatible with the concurrent page allocator.

Instances

Monad m => MonadReader MemoryStoreConfig (MemoryStoreT fp m) Source # 
(Applicative m, Monad m, MonadIO m, MonadThrow m, Ord fp, Show fp, Typeable * fp) => StoreM fp (MemoryStoreT fp m) Source # 

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 #

Monad m => Monad (MemoryStoreT fp m) Source # 

Methods

(>>=) :: MemoryStoreT fp m a -> (a -> MemoryStoreT fp m b) -> MemoryStoreT fp m b #

(>>) :: MemoryStoreT fp m a -> MemoryStoreT fp m b -> MemoryStoreT fp m b #

return :: a -> MemoryStoreT fp m a #

fail :: String -> MemoryStoreT fp m a #

Functor m => Functor (MemoryStoreT fp m) Source # 

Methods

fmap :: (a -> b) -> MemoryStoreT fp m a -> MemoryStoreT fp m b #

(<$) :: a -> MemoryStoreT fp m b -> MemoryStoreT fp m a #

Applicative m => Applicative (MemoryStoreT fp m) Source # 

Methods

pure :: a -> MemoryStoreT fp m a #

(<*>) :: MemoryStoreT fp m (a -> b) -> MemoryStoreT fp m a -> MemoryStoreT fp m b #

(*>) :: MemoryStoreT fp m a -> MemoryStoreT fp m b -> MemoryStoreT fp m b #

(<*) :: MemoryStoreT fp m a -> MemoryStoreT fp m b -> MemoryStoreT fp m a #

MonadIO m => MonadIO (MemoryStoreT fp m) Source # 

Methods

liftIO :: IO a -> MemoryStoreT fp m a #

MonadThrow m => MonadThrow (MemoryStoreT fp m) Source # 

Methods

throwM :: Exception e => e -> MemoryStoreT fp m a #

MonadCatch m => MonadCatch (MemoryStoreT fp m) Source # 

Methods

catch :: Exception e => MemoryStoreT fp m a -> (e -> MemoryStoreT fp m a) -> MemoryStoreT fp m a #

MonadMask m => MonadMask (MemoryStoreT fp m) Source # 

Methods

mask :: ((forall a. MemoryStoreT fp m a -> MemoryStoreT fp m a) -> MemoryStoreT fp m b) -> MemoryStoreT fp m b #

uninterruptibleMask :: ((forall a. MemoryStoreT fp m a -> MemoryStoreT fp m a) -> MemoryStoreT fp m b) -> MemoryStoreT fp m b #

(Applicative m, Monad m, MonadIO m, MonadCatch m) => ConcurrentMetaStoreM (MemoryStoreT FilePath m) Source # 

runMemoryStoreT Source #

Arguments

:: MemoryStoreT fp m a

Action to run

-> MemoryStoreConfig

Configuration

-> MemoryFiles fp

Data

-> m a 

Run the storage operations in the MemoryStoreT monad, given a collection of Files.

newEmptyMemoryStore :: IO (MemoryFiles hnd) Source #

Construct a store with an empty database with name of type hnd.

Exceptions

newtype FileNotFoundError hnd Source #

Exception thrown when a file is accessed that doesn't exist.

Constructors

FileNotFoundError hnd 

data PageNotFoundError hnd Source #

Exception thrown when a page that is accessed doesn't exist.

Constructors

PageNotFoundError hnd PageId