Safe Haskell | Trustworthy |
---|
An I-Structure, also known as an array of IVars, implemented using a boxed vector.
- data IStructure s a
- newIStructure :: Int -> Par d s (IStructure s elt)
- newIStructureWithCallback :: Int -> (Int -> elt -> Par d s ()) -> Par d s (IStructure s elt)
- put :: (NFData elt, Eq elt) => IStructure s elt -> Int -> elt -> Par d s ()
- put_ :: Eq elt => IStructure s elt -> Int -> elt -> Par d s ()
- get :: Eq elt => IStructure s elt -> Int -> Par d s elt
- getLength :: IStructure s a -> Par d s Int
- forEachHP :: Maybe HandlerPool -> IStructure s a -> (Int -> a -> Par d s ()) -> Par d s ()
- freezeIStructure :: IStructure s a -> Par QuasiDet s (Vector (Maybe a))
Documentation
data IStructure s a Source
An I-Structure, also known as an array of IVars.
LVarData1 IStructure | An |
OrderedLVarData1 IStructure | The |
Foldable (IStructure Trvrsbl) | |
Foldable (IStructure Frzn) | |
Eq (IStructure s v) | |
Show a => Show (IStructure Trvrsbl a) | For convenience only; the user could define this. |
Show a => Show (IStructure Frzn a) | |
DeepFrz a => DeepFrz (IStructure s a) |
Basic operations
newIStructure :: Int -> Par d s (IStructure s elt)Source
Create a new, empty, monotonically growing IStructure
of a given size.
All entries start off as zero, which must be "bottom".
newIStructureWithCallback :: Int -> (Int -> elt -> Par d s ()) -> Par d s (IStructure s elt)Source
Register handlers on each internal IVar as it is created.
This operation should be more efficient than newIStructure
followed by forEachHP
.
put :: (NFData elt, Eq elt) => IStructure s elt -> Int -> elt -> Par d s ()Source
Put a single element in the IStructure
at a given index. This variant is deeply strict (NFData
).
put_ :: Eq elt => IStructure s elt -> Int -> elt -> Par d s ()Source
Put a single element in the IStructure
at a given index. That index must be previously empty. (WHNF)
Strict in the element being put in the set.
get :: Eq elt => IStructure s elt -> Int -> Par d s eltSource
Wait for the indexed entry to contain a value, and return that value.
getLength :: IStructure s a -> Par d s IntSource
Retrieve the number of slots in the IStructure
.
Iteration and callbacks
:: Maybe HandlerPool | pool to enroll in, if any |
-> IStructure s a |
|
-> (Int -> a -> Par d s ()) | callback |
-> Par d s () |
Add an (asynchronous) callback that listens for all new elements added to
the IStructure
, optionally enrolled in a handler pool.
Freezing
freezeIStructure :: IStructure s a -> Par QuasiDet s (Vector (Maybe a))Source
O(N) complexity, unfortunately. This implementation of IStructure
s requires
freezing each of the individual IVars stored in the array.