Safe Haskell | None |
---|---|
Language | Haskell2010 |
Environments of a read or write transaction.
- data StateType
- data S t 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)
- fileStateFreedDirtyPages :: !(S stateType (Set DirtyFree))
- fileStateFreeTree :: !(S stateType FreeTree)
- fileStateDirtyReusablePages :: !(Set DirtyOldFree)
- fileStateReusablePages :: ![OldFree]
- fileStateReusablePagesTxId :: !(Maybe TxId)
- data WriterEnv hnds = WriterEnv {
- writerHnds :: !hnds
- writerTxId :: !TxId
- writerReaders :: Map TxId Integer
- writerIndexFileState :: FileState TypeIndex
- writerDataFileState :: FileState TypeData
- writerReusablePagesOn :: !Bool
- writerDirtyOverflows :: !(Set DirtyOverflow)
- writerOverflowCounter :: !Word32
- writerRemovedOverflows :: ![OldOverflow]
- newWriter :: hnd -> TxId -> Map TxId Integer -> S TypeData PageId -> S TypeIndex PageId -> S TypeData (Set DirtyFree) -> S TypeIndex (Set DirtyFree) -> S TypeData FreeTree -> S TypeIndex FreeTree -> WriterEnv hnd
- newtype Fresh = Fresh PageId
- newtype NewlyFreed = NewlyFreed PageId
- newtype Dirty = Dirty PageId
- newtype DirtyFree = DirtyFree PageId
- newtype OldFree = OldFree PageId
- newtype DirtyOldFree = DirtyOldFree PageId
- data SomeFreePage
- getSomeFreePageId :: SomeFreePage -> PageId
- freePage :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m ()
- updateFileState :: FileState t -> (forall a. a -> S t a) -> Maybe Dirty -> Maybe DirtyOldFree -> PageId -> FileState t
- dirty :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m (Maybe Dirty)
- dirtyOldFree :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m (Maybe DirtyOldFree)
- touchPage :: MonadState (WriterEnv hnd) m => S stateType SomeFreePage -> 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
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 (Set DirtyFree) -> S TypeIndex (Set DirtyFree) -> S TypeData FreeTree -> S TypeIndex FreeTree -> WriterEnv hnd Source #
Create a new writer.
Wrapper around PageId
indicating it is a fresh page, allocated at the
end of the database.
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 a dirty page.
Wrapper around PageId
indicating the page is dirty and free for reuse.
Wrapper around PageId
inidcating it was fetched from the free database
and is ready for reuse.
newtype DirtyOldFree Source #
Wrapper around PageId
indicating it wa fetched from the free database
and is actually dirty.
data SomeFreePage Source #
A sum type repesenting any type of free page, that can immediately be used to write something to.
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 DirtyFree
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 -> Maybe DirtyOldFree -> 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.
dirtyOldFree :: (Functor m, MonadState (WriterEnv hnd) m) => S stateType PageId -> m (Maybe DirtyOldFree) Source #
Get a DirtyOldFree
page, by first proving it is in fact a dirty old free page.
touchPage :: MonadState (WriterEnv hnd) m => S stateType SomeFreePage -> 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.