lvish-1.1.4: Parallel scheduler, LVar data structures, and infrastructure to build more.

Safe HaskellTrustworthy
LanguageHaskell98

Data.LVar.SatMap

Description

Saturating maps. These store pure (joinable) values, but when a join fails the map fails (saturates), after which it requires only a small, constant amount of memory.

Synopsis

Documentation

class PartialJoinSemiLattice a where Source

A partial version of Algebra.Lattice.JoinSemiLattice, this could be made into a complete lattice by the addition of a top element.

Methods

joinMaybe :: a -> a -> Maybe a Source

newtype SatMap k s v Source

The map datatype itself. Like all other LVars, it has an s parameter (think STRef) in addition to the a parameter that describes the type of elements in the set.

Performance note: There is only one mutable location in this implementation. Thus it is not a scalable implementation.

Constructors

SatMap (LVar s (IORef (SatMapContents k v)) (k, v)) 

Instances

LVarData1 (SatMap k)

An SatMap can be treated as a generic container LVar. However, the polymorphic operations are less useful than the monomorphic ones exposed by this module.

OrderedLVarData1 (SatMap k)

The SatMaps in this module also have the special property that they support an O(1) freeze operation which immediately yields a Foldable container (snapFreeze).

Foldable (SatMap k Trvrsbl) 
Foldable (SatMap k Frzn)

As with all LVars, after freezing, map elements can be consumed. In the case of this SatMap implementation, it need only be Frzn, not Trvrsbl.

Eq (SatMap k s v)

Equality is physical equality, as with IORefs.

(Show k, Show a) => Show (SatMap k Trvrsbl a)

For convenience only; the user could define this.

(Show k, Show a) => Show (SatMap k Frzn a) 
DeepFrz a => DeepFrz (SatMap k s a) 
type FrzType (SatMap k s a) = SatMap k Frzn a 

type SatMapContents k v = Maybe (Map k v, OnSat) Source

type OnSat = Par () Source

Callback to execute when saturating occurs.

forEachHP Source

Arguments

:: Maybe HandlerPool

optional pool to enroll in

-> SatMap k s v

Map to listen to

-> (k -> v -> Par d s ())

callback

-> Par d s () 

Add an (asynchronous) callback that listens for all new key/value pairs added to the map, optionally enrolled in a handler pool.

newEmptyMap :: Par d s (SatMap k s v) Source

Create a fresh map with nothing in it.

newMap :: Map k v -> Par d s (SatMap k s v) Source

Create a new map populated with initial elements.

newFromList :: (Ord k, Eq v) => [(k, v)] -> Par d s (SatMap k s v) Source

A convenience function that is equivalent to calling fromList followed by newMap.

withCallbacksThenFreeze :: forall k v b s. Eq b => SatMap k s v -> (k -> v -> QPar s ()) -> QPar s b -> QPar s b Source

Register a per-element callback, then run an action in this context, and freeze when all (recursive) invocations of the callback are complete. Returns the final value of the provided action.

forEach :: SatMap k s v -> (k -> v -> Par d s ()) -> Par d s () Source

Add an (asynchronous) callback that listens for all new new key/value pairs added to the map.

insert :: (Ord k, PartialJoinSemiLattice v, Eq v) => k -> v -> SatMap k s v -> Par d s () Source

Put a single entry into the map. Strict (WHNF) in the key and value.

As with other container LVars, if a key is inserted multiple times, the values had better be equal (==), or a multiple-put error is raised.

whenSat :: SatMap k s v -> Par d s () -> Par d s () Source

Register a callback that is only called if the SatMap LVar becomes saturated.

saturate :: SatMap k s v -> Par d s () Source

Drive the variable to top. This is equivalent to an insert of a conflicting binding.

fromIMap :: SatMap k Frzn a -> Maybe (Map k a) Source

O(1): Convert from an SatMap to a plain Map. This is only permitted when the SatMap has already been frozen. This is useful for processing the result of runParThenFreeze.