| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- 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.
Constructors
| 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 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.
Constructors
| MemoryStoreConfig | |
Instances
| Show MemoryStoreConfig Source # | |
Defined in Database.Haskey.Store.InMemory Methods showsPrec :: Int -> MemoryStoreConfig -> ShowS # show :: MemoryStoreConfig -> String # showList :: [MemoryStoreConfig] -> ShowS # | |
| Monad m => MonadReader MemoryStoreConfig (MemoryStoreT fp m) Source # | |
Defined in Database.Haskey.Store.InMemory Methods ask :: MemoryStoreT fp m MemoryStoreConfig # local :: (MemoryStoreConfig -> MemoryStoreConfig) -> MemoryStoreT fp m a -> MemoryStoreT fp m a # reader :: (MemoryStoreConfig -> a) -> MemoryStoreT fp m a # | |
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
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 |
Instances
| Show hnd => Show (FileNotFoundError hnd) Source # | |
Defined in Database.Haskey.Store.InMemory Methods showsPrec :: Int -> FileNotFoundError hnd -> ShowS # show :: FileNotFoundError hnd -> String # showList :: [FileNotFoundError hnd] -> ShowS # | |
| (Typeable hnd, Show hnd) => Exception (FileNotFoundError hnd) Source # | |
Defined in Database.Haskey.Store.InMemory Methods toException :: FileNotFoundError hnd -> SomeException # fromException :: SomeException -> Maybe (FileNotFoundError hnd) # displayException :: FileNotFoundError hnd -> String # | |
data PageNotFoundError hnd Source #
Exception thrown when a page that is accessed doesn't exist.
Constructors
| PageNotFoundError hnd PageId |
Instances
| Show hnd => Show (PageNotFoundError hnd) Source # | |
Defined in Database.Haskey.Store.InMemory Methods showsPrec :: Int -> PageNotFoundError hnd -> ShowS # show :: PageNotFoundError hnd -> String # showList :: [PageNotFoundError hnd] -> ShowS # | |
| (Typeable hnd, Show hnd) => Exception (PageNotFoundError hnd) Source # | |
Defined in Database.Haskey.Store.InMemory Methods toException :: PageNotFoundError hnd -> SomeException # fromException :: SomeException -> Maybe (PageNotFoundError hnd) # displayException :: PageNotFoundError hnd -> String # | |
data WrongNodeTypeError Source #
Exception thrown when a node cannot be cast to the right type.
As used in getNodePage.
Constructors
| WrongNodeTypeError |
Instances
| Show WrongNodeTypeError Source # | |
Defined in Database.Haskey.Store.InMemory Methods showsPrec :: Int -> WrongNodeTypeError -> ShowS # show :: WrongNodeTypeError -> String # showList :: [WrongNodeTypeError] -> ShowS # | |
| Exception WrongNodeTypeError Source # | |
Defined in Database.Haskey.Store.InMemory Methods toException :: WrongNodeTypeError -> SomeException # fromException :: SomeException -> Maybe WrongNodeTypeError # | |
data WrongOverflowValueError Source #
Exception thrown when a value from an overflow page cannot be cast.
As used in getOverflow.
Constructors
| WrongOverflowValueError |
Instances
| Show WrongOverflowValueError Source # | |
Defined in Database.Haskey.Store.InMemory Methods showsPrec :: Int -> WrongOverflowValueError -> ShowS # show :: WrongOverflowValueError -> String # showList :: [WrongOverflowValueError] -> ShowS # | |
| Exception WrongOverflowValueError Source # | |
Defined in Database.Haskey.Store.InMemory | |