| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Haskey
Description
A monad transformer supporting Haskey transactions.
See https://github.com/haskell-haskey/haskey-mtl/blob/master/example/Main.hs for a complete example.
- module Database.Haskey.Alloc.Transaction
- class Monad m => MonadHaskey root m | m -> root where
- data HaskeyT root m a
- runFileStoreHaskeyT :: (Root root, MonadMask m, MonadIO m) => HaskeyT root m a -> ConcurrentDb root -> FileStoreConfig -> m a
- data FileStoreT fp m a :: * -> (* -> *) -> * -> *
- data FileStoreConfig :: *
- runFileStoreT :: Monad m => FileStoreT FilePath m a -> FileStoreConfig -> m a
- defFileStoreConfig :: FileStoreConfig
- data ConcurrentDb root :: * -> *
- concurrentHandles :: FilePath -> ConcurrentHandles
- openConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (Maybe (ConcurrentDb root))
- createConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> root -> m (ConcurrentDb root)
Re-exports
Monad
class Monad m => MonadHaskey root m | m -> root where Source #
A monad supporting database transactions.
The type root is the data type holding the roots of the database trees.
Minimal complete definition
Methods
transact :: Root root => (forall n. (AllocM n, MonadMask n) => root -> n (Transaction root a)) -> m a Source #
transact_ :: Root root => (forall n. (AllocM n, MonadMask n) => root -> n (Transaction root ())) -> m () Source #
transactReadOnly :: Root root => (forall n. (AllocReaderM n, MonadMask n) => root -> n a) -> m a Source #
Instances
| (Monoid w, MonadHaskey root m) => MonadHaskey root (WriterT w m) Source # | |
| (Monoid w, MonadHaskey root m) => MonadHaskey root (WriterT w m) Source # | |
| MonadHaskey root m => MonadHaskey root (StateT s m) Source # | |
| MonadHaskey root m => MonadHaskey root (StateT s m) Source # | |
| (Root root, Applicative m, MonadMask m, MonadIO m) => MonadHaskey root (HaskeyT root m) Source # | |
| MonadHaskey root m => MonadHaskey root (ReaderT * r m) Source # | |
| (Monoid w, MonadHaskey root m) => MonadHaskey root (RWST r w s m) Source # | |
| (Monoid w, MonadHaskey root m) => MonadHaskey root (RWST r w s m) Source # | |
data HaskeyT root m a Source #
A monad transformer that is an instance of MonadHaskey.
The root is the data type holding the roots of the database trees.
Instances
| MonadRWS r w s m => MonadRWS r w s (HaskeyT root m) Source # | |
| MonadReader r m => MonadReader r (HaskeyT root m) Source # | |
| MonadState s m => MonadState s (HaskeyT root m) Source # | |
| MonadWriter w m => MonadWriter w (HaskeyT root m) Source # | |
| (Root root, Applicative m, MonadMask m, MonadIO m) => MonadHaskey root (HaskeyT root m) Source # | |
| MonadTrans (HaskeyT root) Source # | |
| Monad m => Monad (HaskeyT root m) Source # | |
| Functor m => Functor (HaskeyT root m) Source # | |
| Applicative m => Applicative (HaskeyT root m) Source # | |
| MonadIO m => MonadIO (HaskeyT root m) Source # | |
| MonadThrow m => MonadThrow (HaskeyT root m) Source # | |
| MonadCatch m => MonadCatch (HaskeyT root m) Source # | |
| MonadMask m => MonadMask (HaskeyT root m) Source # | |
runFileStoreHaskeyT :: (Root root, MonadMask m, MonadIO m) => HaskeyT root m a -> ConcurrentDb root -> FileStoreConfig -> m a Source #
Run Haskey transactions, backed by a file store.
Open and create (re-exports)
data FileStoreT fp m a :: * -> (* -> *) -> * -> * #
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
| (Applicative m, Monad m, MonadIO m, MonadThrow m) => StoreM FilePath (FileStoreT FilePath m) | |
| Monad m => MonadReader FileStoreConfig (FileStoreT fp m) | |
| Monad m => MonadState (Files fp) (FileStoreT fp m) | |
| Monad m => Monad (FileStoreT fp m) | |
| Functor m => Functor (FileStoreT fp m) | |
| Monad m => Applicative (FileStoreT fp m) | |
| MonadIO m => MonadIO (FileStoreT fp m) | |
| MonadThrow m => MonadThrow (FileStoreT fp m) | |
| MonadCatch m => MonadCatch (FileStoreT fp m) | |
| MonadMask m => MonadMask (FileStoreT fp m) | |
| (Applicative m, Monad m, MonadIO m, MonadCatch m) => ConcurrentMetaStoreM (FileStoreT FilePath m) | |
data FileStoreConfig :: * #
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.
Instances
| Show FileStoreConfig | |
| Monad m => MonadReader FileStoreConfig (FileStoreT fp m) | |
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.
defFileStoreConfig :: FileStoreConfig #
The default configuration
This is an unwrapped fileStoreConfigWithPageSize with a page size of 4096
bytes.
data ConcurrentDb root :: * -> * #
An active concurrent database.
This can be shared amongst threads.
concurrentHandles :: FilePath -> ConcurrentHandles #
Construct a set of ConcurrentHandles from a root directory.
openConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> m (Maybe (ConcurrentDb root)) #
Open the an existing database, with the given handles.
createConcurrentDb :: (Root root, MonadIO m, MonadMask m, ConcurrentMetaStoreM m) => ConcurrentHandles -> root -> m (ConcurrentDb root) #
Open a new concurrent database, with the given handles.