| 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).
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
- data FileStoreConfig = FileStoreConfig {}
- defFileStoreConfig :: FileStoreConfig
- fileStoreConfigWithPageSize :: PageSize -> Maybe FileStoreConfig
- data FileStoreT fp m a
- runFileStoreT :: Monad m => FileStoreT FilePath m a -> FileStoreConfig -> m a
- encodeAndPad :: PageSize -> Page t -> Maybe ByteString
- newtype FileNotFoundError hnd = FileNotFoundError hnd
- data PageOverflowError = PageOverflowError
- 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 |
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 # | |
Defined in Database.Haskey.Store.File Methods showsPrec :: Int -> FileStoreConfig -> ShowS # show :: FileStoreConfig -> String # showList :: [FileStoreConfig] -> ShowS # | |
| Monad m => MonadReader FileStoreConfig (FileStoreT fp m) Source # | |
Defined in Database.Haskey.Store.File Methods ask :: FileStoreT fp m FileStoreConfig # local :: (FileStoreConfig -> FileStoreConfig) -> FileStoreT fp m a -> FileStoreT fp m a # reader :: (FileStoreConfig -> a) -> FileStoreT fp m a # | |
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
Arguments
| :: Monad m | |
| => FileStoreT FilePath m a | Action |
| -> FileStoreConfig | Configuration |
| -> m a |
Run the storage operations in the FileStoreT monad, given a collection of
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 |
Instances
| Show hnd => Show (FileNotFoundError hnd) Source # | |
Defined in Database.Haskey.Store.File 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.File Methods toException :: FileNotFoundError hnd -> SomeException # fromException :: SomeException -> Maybe (FileNotFoundError hnd) # displayException :: FileNotFoundError hnd -> String # | |
data PageOverflowError Source #
Exception thrown when a page that is too large is written.
As used in putNodePage.
Constructors
| PageOverflowError |
Instances
| Show PageOverflowError Source # | |
Defined in Database.Haskey.Store.File Methods showsPrec :: Int -> PageOverflowError -> ShowS # show :: PageOverflowError -> String # showList :: [PageOverflowError] -> ShowS # | |
| Exception PageOverflowError Source # | |
Defined in Database.Haskey.Store.File Methods toException :: PageOverflowError -> SomeException # | |
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.File Methods showsPrec :: Int -> WrongNodeTypeError -> ShowS # show :: WrongNodeTypeError -> String # showList :: [WrongNodeTypeError] -> ShowS # | |
| Exception WrongNodeTypeError Source # | |
Defined in Database.Haskey.Store.File 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.File Methods showsPrec :: Int -> WrongOverflowValueError -> ShowS # show :: WrongOverflowValueError -> String # showList :: [WrongOverflowValueError] -> ShowS # | |
| Exception WrongOverflowValueError Source # | |
Defined in Database.Haskey.Store.File | |