Safe Haskell | None |
---|---|
Language | Haskell2010 |
Environments of a read or write transaction.
- data StateType
- data S (t :: StateType) a where
- getSValue :: S t a -> a
- newtype ReaderEnv hnds = ReaderEnv {
- readerHnds :: hnds
- data FileState stateType = FileState {
- fileStateNewlyFreedPages :: ![NewlyFreed]
- fileStateOriginalNumPages :: !(S stateType PageId)
- fileStateNewNumPages :: !(S stateType PageId)
- fileStateDirtyPages :: !(Set PageId)
- fileStateFreeTree :: !(S stateType FreeTree)
- fileStateCachedFreePages :: !(S stateType [FreePage])
- data WriterEnv hnds = WriterEnv {
- writerHnds :: !hnds
- writerTxId :: !TxId
- writerReaders :: Map TxId Integer
- writerIndexFileState :: FileState TypeIndex
- writerDataFileState :: FileState TypeData
- writerQueryFreeTreeOn :: !Bool
- writerDirtyOverflows :: !(Set DirtyOverflow)
- writerOverflowCounter :: !Word32
- writerRemovedOverflows :: ![OldOverflow]
- newWriter :: hnd -> TxId -> Map TxId Integer -> S TypeData PageId -> S TypeIndex PageId -> S TypeData [FreePage] -> S TypeIndex [FreePage] -> S TypeData FreeTree -> S TypeIndex FreeTree -> WriterEnv hnd
- newtype NewlyFreed = NewlyFreed PageId
- newtype FreePage = FreePage PageId
- newtype Dirty = Dirty PageId
- freePage :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m ()
- updateFileState :: FileState t -> (forall a. a -> S t a) -> Maybe Dirty -> PageId -> FileState t
- dirty :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m (Maybe Dirty)
- touchPage :: MonadState (WriterEnv hnd) m => S stateType PageId -> m ()
- newtype DirtyOverflow = DirtyOverflow OverflowId
- newtype OldOverflow = OldOverflow OverflowId
- touchOverflow :: MonadState (WriterEnv hnd) m => OverflowId -> m ()
- overflowType :: MonadState (WriterEnv hnd) m => OverflowId -> m (Either DirtyOverflow OldOverflow)
- removeOldOverflow :: MonadState (WriterEnv hdn) m => OldOverflow -> m ()
Documentation
data S (t :: StateType) a where Source #
Wrapper around a type to indicate it belongs to a file with either data/leaf nodes or index nodes.
newtype ReaderEnv hnds Source #
ReaderEnv | |
|
data FileState stateType Source #
FileState | |
|
WriterEnv | |
|
newWriter :: hnd -> TxId -> Map TxId Integer -> S TypeData PageId -> S TypeIndex PageId -> S TypeData [FreePage] -> S TypeIndex [FreePage] -> S TypeData FreeTree -> S TypeIndex FreeTree -> WriterEnv hnd Source #
Create a new writer.
newtype NewlyFreed Source #
Wrapper around PageId
indicating it is newly free'd and cannot be reused
in the same transaction.
Wrapper around PageId
indicating it is free and can be reused in any
transaction.
Wrapper around PageId
indicating that it is dirty, i.e. written to in
this transaction.
freePage :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m () Source #
Try to free a page, given a set of dirty pages.
If the page was dirty, a FreePage
page is added to the environment, if
not a NewlyFreed
page is added to the environment.
Btw, give me lenses...
updateFileState :: FileState t -> (forall a. a -> S t a) -> Maybe Dirty -> PageId -> FileState t Source #
dirty :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m (Maybe Dirty) Source #
Get a Dirty
page, by first proving it is in fact dirty.
touchPage :: MonadState (WriterEnv hnd) m => S stateType PageId -> m () Source #
Touch a fresh page, make it dirty.
We really need lenses...
newtype DirtyOverflow Source #
Wrapper around OverflowId
indicating that it is dirty.
newtype OldOverflow Source #
Wrapper around OverflowId
indicating that it is an overflow
page from a previous transaction.
touchOverflow :: MonadState (WriterEnv hnd) m => OverflowId -> m () Source #
Touch a fresh overflow page, making it dirty.
overflowType :: MonadState (WriterEnv hnd) m => OverflowId -> m (Either DirtyOverflow OldOverflow) Source #
Get the type of the overflow page.
removeOldOverflow :: MonadState (WriterEnv hdn) m => OldOverflow -> m () Source #
Free an old overflow page.