haskey-0.1.0.1: A transcatoinal, ACID compliant, embeddable key-value store.

Safe HaskellNone
LanguageHaskell2010

Database.Haskey.Alloc.Concurrent.Environment

Description

Environments of a read or write transaction.

Synopsis

Documentation

data StateType Source #

Constructors

TypeData 
TypeIndex 

data S t a where Source #

Wrapper around a type to indicate it belongs to a file with either data/leaf nodes or index nodes.

Constructors

DataState :: a -> S TypeData a 
IndexState :: a -> S TypeIndex a 

Instances

Functor (S t) Source # 

Methods

fmap :: (a -> b) -> S t a -> S t b #

(<$) :: a -> S t b -> S t a #

Show a => Show (S t a) Source # 

Methods

showsPrec :: Int -> S t a -> ShowS #

show :: S t a -> String #

showList :: [S t a] -> ShowS #

Binary a => Binary (S TypeData a) Source # 

Methods

put :: S TypeData a -> Put #

get :: Get (S TypeData a) #

putList :: [S TypeData a] -> Put #

Binary a => Binary (S TypeIndex a) Source # 

Methods

put :: S TypeIndex a -> Put #

get :: Get (S TypeIndex a) #

putList :: [S TypeIndex a] -> Put #

getSValue :: S t a -> a Source #

newtype ReaderEnv hnds Source #

Constructors

ReaderEnv 

Fields

data FileState stateType Source #

Constructors

FileState 

Fields

data WriterEnv hnds Source #

Constructors

WriterEnv 

Fields

newtype Fresh Source #

Wrapper around PageId indicating it is a fresh page, allocated at the end of the database.

Constructors

Fresh PageId 

Instances

Eq Fresh Source # 

Methods

(==) :: Fresh -> Fresh -> Bool #

(/=) :: Fresh -> Fresh -> Bool #

Ord Fresh Source # 

Methods

compare :: Fresh -> Fresh -> Ordering #

(<) :: Fresh -> Fresh -> Bool #

(<=) :: Fresh -> Fresh -> Bool #

(>) :: Fresh -> Fresh -> Bool #

(>=) :: Fresh -> Fresh -> Bool #

max :: Fresh -> Fresh -> Fresh #

min :: Fresh -> Fresh -> Fresh #

Show Fresh Source # 

Methods

showsPrec :: Int -> Fresh -> ShowS #

show :: Fresh -> String #

showList :: [Fresh] -> ShowS #

newtype NewlyFreed Source #

Wrapper around PageId indicating it is newly free'd and cannot be reused in the same transaction.

Constructors

NewlyFreed PageId 

newtype Dirty Source #

Wrapper around PageId indicating it is a dirty page.

Constructors

Dirty PageId 

Instances

Eq Dirty Source # 

Methods

(==) :: Dirty -> Dirty -> Bool #

(/=) :: Dirty -> Dirty -> Bool #

Ord Dirty Source # 

Methods

compare :: Dirty -> Dirty -> Ordering #

(<) :: Dirty -> Dirty -> Bool #

(<=) :: Dirty -> Dirty -> Bool #

(>) :: Dirty -> Dirty -> Bool #

(>=) :: Dirty -> Dirty -> Bool #

max :: Dirty -> Dirty -> Dirty #

min :: Dirty -> Dirty -> Dirty #

Show Dirty Source # 

Methods

showsPrec :: Int -> Dirty -> ShowS #

show :: Dirty -> String #

showList :: [Dirty] -> ShowS #

newtype OldFree Source #

Wrapper around PageId inidcating it was fetched from the free database and is ready for reuse.

Constructors

OldFree PageId 

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...

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.