Safe Haskell | Unsafe |
---|---|
Language | Haskell98 |
This is not a datatype for the end-user.
Rather, this module is for building new LVar types in a comparatively easy way: by
putting a pure value in a mutable container, and defining a put
operation as a pure
function.
The data structure implementor who uses this module must guarantee
that their put
operation computes a least upper bound, ensuring
that the set of states that their LVar type can take on form a
join-semilattice (http://en.wikipedia.org/wiki/Semilattice).
- newtype PureLVar s t = PureLVar (LVar s (IORef t) t)
- newPureLVar :: JoinSemiLattice t => t -> Par d s (PureLVar s t)
- putPureLVar :: JoinSemiLattice t => PureLVar s t -> t -> Par d s ()
- waitPureLVar :: (JoinSemiLattice t, Eq t) => PureLVar s t -> t -> Par d s ()
- freezePureLVar :: PureLVar s t -> Par QuasiDet s t
- fromPureLVar :: PureLVar Frzn t -> t
- getPureLVar :: (JoinSemiLattice t, Eq t) => PureLVar s t -> [t] -> Par d s t
- unsafeGetPureLVar :: (JoinSemiLattice t, Eq t) => PureLVar s t -> (t -> Bool) -> Par d s t
- verifyFiniteJoin :: (Eq a, Show a) => [a] -> (a -> a -> a) -> Maybe String
- verifyFiniteGet :: (Eq a, Show a, JoinSemiLattice a, Eq b, Show b) => [a] -> (b, b) -> (a -> b) -> Maybe String
Documentation
An LVar which consists merely of an immutable, pure value inside a mutable box.
newPureLVar :: JoinSemiLattice t => t -> Par d s (PureLVar s t) Source
A new pure LVar populated with the provided initial state.
putPureLVar :: JoinSemiLattice t => PureLVar s t -> t -> Par d s () Source
Put a new value which will be joined with the old.
waitPureLVar :: (JoinSemiLattice t, Eq t) => PureLVar s t -> t -> Par d s () Source
Wait until the pure LVar has crossed a threshold and then unblock. (In the semantics, this is a singleton query set.)
freezePureLVar :: PureLVar s t -> Par QuasiDet s t Source
Freeze the pure LVar, returning its exact value.
Subsequent put
s will raise an error.
fromPureLVar :: PureLVar Frzn t -> t Source
Read the exact contents of an already frozen PureLVar.
getPureLVar :: (JoinSemiLattice t, Eq t) => PureLVar s t -> [t] -> Par d s t Source
Blocks until the contents of lv
are at or above one element of
thrshSet
, then returns that one element.
unsafeGetPureLVar :: (JoinSemiLattice t, Eq t) => PureLVar s t -> (t -> Bool) -> Par d s t Source
Like getPureLVar
but uses a threshold function rather than an explicit set.
Verifying lattice structure
verifyFiniteJoin :: (Eq a, Show a) => [a] -> (a -> a -> a) -> Maybe String Source
Takes a finite set of states and a join operation (e.g., for an instance of JoinSemiLattice) and returns an error message if the join-semilattice properties don't hold.
verifyFiniteGet :: (Eq a, Show a, JoinSemiLattice a, Eq b, Show b) => [a] -> (b, b) -> (a -> b) -> Maybe String Source
Verify that a blocking get is monotone in just the right way. This takes a designated bottom and top element.