Safe Haskell | None |
---|---|
Language | Haskell2010 |
Binary in-memory storage back-end. Can be used as a storage back-end for the append-only page allocator (see Data.BTree.Alloc).
- data Page (t :: PageType) where
- EmptyPage :: Page TypeEmpty
- ConcurrentMetaPage :: Root root => ConcurrentMeta root -> Page TypeConcurrentMeta
- OverflowPage :: Value v => v -> Page TypeOverflow
- LeafNodePage :: (Key k, Value v) => Height Z -> Node Z k v -> Page TypeLeafNode
- IndexNodePage :: (Key k, Value v) => Height (S h) -> Node (S h) k v -> Page TypeIndexNode
- type MemoryFile = Map PageId ByteString
- type MemoryFiles fp = MVar (Map fp MemoryFile)
- data MemoryStoreConfig = MemoryStoreConfig {}
- defMemoryStoreConfig :: MemoryStoreConfig
- memoryStoreConfigWithPageSize :: PageSize -> Maybe MemoryStoreConfig
- data MemoryStoreT fp m a
- runMemoryStoreT :: MemoryStoreT fp m a -> MemoryStoreConfig -> MemoryFiles fp -> m a
- newEmptyMemoryStore :: IO (MemoryFiles hnd)
- newtype FileNotFoundError hnd = FileNotFoundError hnd
- data PageNotFoundError hnd = PageNotFoundError hnd PageId
- data WrongNodeTypeError = WrongNodeTypeError
- data WrongOverflowValueError = WrongOverflowValueError
Storage
data Page (t :: PageType) where Source #
A decoded page, of a certain type t
of kind PageType
.
EmptyPage :: Page TypeEmpty | |
ConcurrentMetaPage :: Root root => ConcurrentMeta root -> Page TypeConcurrentMeta | |
OverflowPage :: Value v => v -> Page TypeOverflow | |
LeafNodePage :: (Key k, Value v) => Height Z -> Node Z k v -> Page TypeLeafNode | |
IndexNodePage :: (Key k, Value v) => Height (S h) -> Node (S h) k v -> Page TypeIndexNode |
type MemoryFile = Map PageId ByteString Source #
A file containing a collection of pages.
type MemoryFiles fp = MVar (Map fp MemoryFile) Source #
A collection of File
s, 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
.
Show MemoryStoreConfig Source # | |
Monad m => MonadReader MemoryStoreConfig (MemoryStoreT fp m) Source # | |
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.
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 # | |
Monad m => Monad (MemoryStoreT fp m) Source # | |
Functor m => Functor (MemoryStoreT fp m) Source # | |
Applicative m => Applicative (MemoryStoreT fp m) Source # | |
MonadIO m => MonadIO (MemoryStoreT fp m) Source # | |
MonadThrow m => MonadThrow (MemoryStoreT fp m) Source # | |
MonadCatch m => MonadCatch (MemoryStoreT fp m) Source # | |
MonadMask m => MonadMask (MemoryStoreT fp m) Source # | |
(Applicative m, Monad m, MonadIO m, MonadCatch m) => ConcurrentMetaStoreM (MemoryStoreT FilePath m) Source # | |
:: 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
File
s.
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.
data PageNotFoundError hnd Source #
Exception thrown when a page that is accessed doesn't exist.
data WrongNodeTypeError Source #
Exception thrown when a node cannot be cast to the right type.
As used in getNodePage
.
data WrongOverflowValueError Source #
Exception thrown when a value from an overflow page cannot be cast.
As used in getOverflow
.