| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Haskey.Store.File
Contents
Description
On-disk storage back-end. Can be used as a storage back-end for the append-only page allocator (see Data.BTree.Alloc).
- data Page t where
- EmptyPage :: Page TypeEmpty
 - ConcurrentMetaPage :: (Key k, Value v) => ConcurrentMeta k v -> 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 Files fp = IORef (Map fp FHandle)
 - data FileStoreConfig = FileStoreConfig {}
 - defFileStoreConfig :: FileStoreConfig
 - fileStoreConfigWithPageSize :: PageSize -> Maybe FileStoreConfig
 - data FileStoreT fp m a
 - runFileStoreT :: FileStoreT fp m a -> FileStoreConfig -> Files fp -> m a
 - newFileStore :: IO (Files fp)
 - encodeAndPad :: PageSize -> Page t -> Maybe ByteString
 - newtype FileNotFoundError hnd = FileNotFoundError hnd
 - data PageOverflowError = PageOverflowError
 - data WrongNodeTypeError = WrongNodeTypeError
 - data WrongOverflowValueError = WrongOverflowValueError
 
Storage
A decoded page, of a certain type t of kind PageType.
Constructors
| EmptyPage :: Page TypeEmpty | |
| ConcurrentMetaPage :: (Key k, Value v) => ConcurrentMeta k v -> 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 Files fp = IORef (Map fp FHandle) Source #
A collection of files, each associated with a certain fp handle.
Each file is a Handle opened in ReadWriteMode and contains a
 collection of physical pages.
These files can be safely shared between threads.
data FileStoreConfig Source #
File store configuration.
The default configuration can be obtained by using defFileStoreConfig
A configuration with a specific page size can be obtained by using
 fileStoreConfigWithPageSize.
Constructors
| FileStoreConfig | |
Instances
| Show FileStoreConfig Source # | |
| Monad m => MonadReader FileStoreConfig (FileStoreT fp m) Source # | |
defFileStoreConfig :: FileStoreConfig Source #
The default configuration
This is an unwrapped fileStoreConfigWithPageSize with a page size of 4096
 bytes.
fileStoreConfigWithPageSize :: PageSize -> Maybe FileStoreConfig 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 FileStoreT fp m a Source #
Monad in which on-disk 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 FileStoreConfig (FileStoreT fp m) Source # | |
| (Applicative m, Monad m, MonadIO m, MonadThrow m) => StoreM FilePath (FileStoreT FilePath m) Source # | |
| Monad m => Monad (FileStoreT fp m) Source # | |
| Functor m => Functor (FileStoreT fp m) Source # | |
| Applicative m => Applicative (FileStoreT fp m) Source # | |
| MonadIO m => MonadIO (FileStoreT fp m) Source # | |
| MonadThrow m => MonadThrow (FileStoreT fp m) Source # | |
| MonadCatch m => MonadCatch (FileStoreT fp m) Source # | |
| MonadMask m => MonadMask (FileStoreT fp m) Source # | |
| (Applicative m, Monad m, MonadIO m, MonadCatch m) => ConcurrentMetaStoreM (FileStoreT FilePath m) Source # | |
Arguments
| :: FileStoreT fp m a | Action  | 
| -> FileStoreConfig | Configuration  | 
| -> Files fp | Open files  | 
| -> m a | 
Run the storage operations in the FileStoreT monad, given a collection of
 open files.
newFileStore :: IO (Files fp) Source #
An empty file store, with no open files.
Binary encoding
encodeAndPad :: PageSize -> Page t -> Maybe ByteString Source #
Encode a page padding it to the maxim page size.
Return Nothing of the page is too large to fit into one page size.
Exceptions
newtype FileNotFoundError hnd Source #
Exception thrown when a file is accessed that doesn't exist.
Constructors
| FileNotFoundError hnd | 
data PageOverflowError Source #
Exception thrown when a page that is too large is written.
As used in putNodePage.
Constructors
| PageOverflowError | 
Instances
data WrongNodeTypeError Source #
Exception thrown when a node cannot be cast to the right type.
As used in getNodePage.
Constructors
| WrongNodeTypeError | 
Instances
data WrongOverflowValueError Source #
Exception thrown when a value from an overflow page cannot be cast.
As used in getOverflow.
Constructors
| WrongOverflowValueError |