| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Haskey.Alloc.Concurrent.Monad
Description
This module implements the ConcurrentT monad.
The ConcurrentT monad is used to implement a page allocator with
concurrent readers and serialized writers.
- data ConcurrentHandles = ConcurrentHandles {}
- concurrentHandles :: FilePath -> ConcurrentHandles
- newtype ConcurrentT env hnd m a = ConcurrentT {
- fromConcurrentT :: StateT (env hnd) m a
- runConcurrentT :: ConcurrentMetaStoreM m => ConcurrentT env ConcurrentHandles m a -> env ConcurrentHandles -> m (a, env ConcurrentHandles)
- evalConcurrentT :: ConcurrentMetaStoreM m => ConcurrentT env ConcurrentHandles m a -> env ConcurrentHandles -> m a
- readOverflow' :: (ConcurrentMetaStoreM m, Value v) => FilePath -> OverflowId -> ConcurrentT env hnd m v
- getWriterHnd :: MonadState (WriterEnv ConcurrentHandles) m => Height height -> m FilePath
- getReaderHnd :: MonadState (ReaderEnv ConcurrentHandles) m => Height height -> m FilePath
Documentation
data ConcurrentHandles Source #
All necessary database handles.
Constructors
| ConcurrentHandles | |
Instances
concurrentHandles :: FilePath -> ConcurrentHandles Source #
Construct a set of ConcurrentHandles from a root directory.
newtype ConcurrentT env hnd m a Source #
Monad in which page allocations can take place.
The monad has access to a ConcurrentMetaStoreM back-end which manages can
store and retreive the corresponding metadata.
Constructors
| ConcurrentT | |
Fields
| |
Instances
| Monad m => MonadState (env hnd) (ConcurrentT env hnd m) Source # | |
| MonadTrans (ConcurrentT env hnd) Source # | |
| Monad m => Monad (ConcurrentT env hnd m) Source # | |
| Functor m => Functor (ConcurrentT env hnd m) Source # | |
| Monad m => Applicative (ConcurrentT env hnd m) Source # | |
| MonadIO m => MonadIO (ConcurrentT env hnd m) Source # | |
| MonadThrow m => MonadThrow (ConcurrentT env hnd m) Source # | |
| MonadCatch m => MonadCatch (ConcurrentT env hnd m) Source # | |
| MonadMask m => MonadMask (ConcurrentT env hnd m) Source # | |
| ConcurrentMetaStoreM m => AllocReaderM (ConcurrentT WriterEnv ConcurrentHandles m) Source # | |
| ConcurrentMetaStoreM m => AllocReaderM (ConcurrentT ReaderEnv ConcurrentHandles m) Source # | |
| (ConcurrentMetaStoreM m, MonadIO m) => AllocM (ConcurrentT WriterEnv ConcurrentHandles m) Source # | |
runConcurrentT :: ConcurrentMetaStoreM m => ConcurrentT env ConcurrentHandles m a -> env ConcurrentHandles -> m (a, env ConcurrentHandles) Source #
Run the actions in an ConcurrentT monad, given a reader or writer
environment.
evalConcurrentT :: ConcurrentMetaStoreM m => ConcurrentT env ConcurrentHandles m a -> env ConcurrentHandles -> m a Source #
Evaluate the actions in an ConcurrentT monad, given a reader or writer
environment.
readOverflow' :: (ConcurrentMetaStoreM m, Value v) => FilePath -> OverflowId -> ConcurrentT env hnd m v Source #
getWriterHnd :: MonadState (WriterEnv ConcurrentHandles) m => Height height -> m FilePath Source #
getReaderHnd :: MonadState (ReaderEnv ConcurrentHandles) m => Height height -> m FilePath Source #