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

Safe HaskellTrustworthy

Data.LVar.PureMap

Contents

Description

This module provides finite maps that only grow. It is based on the popular Data.Map balanced-tree representation of maps. Thus scalability is not good for this implementation. However, there are some interoperability benefits. For example, after running a parallel computation with a map result, this module can produce a Map in O(1) without copying, which may be useful downstream.

Synopsis

Basic operations

newtype IMap 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

IMap (LVar s (IORef (Map k v)) (k, v)) 

Instances

LVarData1 (IMap k)

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

OrderedLVarData1 (IMap k)

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

Foldable (IMap k Trvrsbl) 
Foldable (IMap k Frzn) 
Eq (IMap k s v)

Equality is physical equality, as with IORefs.

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

For convenience only; the user could define this.

(Show k, Show a) => Show (IMap k Frzn a) 
DeepFrz a => DeepFrz (IMap k s a) 

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

Create a fresh map with nothing in it.

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

Create a new map populated with initial elements.

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

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

insert :: (Ord k, Eq v) => k -> v -> IMap 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.

getKey :: Ord k => k -> IMap k s v -> Par d s vSource

Wait for the map to contain a specified key, and return the associated value.

waitValue :: (Ord k, Eq v) => v -> IMap k s v -> Par d s ()Source

Wait until the map contains a certain value (on any key).

waitSize :: Int -> IMap k s v -> Par d s ()Source

Wait on the size of the map, not its contents.

modifySource

Arguments

:: forall f a b d s key . (Ord key, LVarData1 f, Show key, Ord a) 
=> IMap key s (f s a) 
-> key

The key to lookup.

-> Par d s (f s a)

Create a new "bottom" element whenever an entry is not present.

-> (f s a -> Par d s b)

The computation to apply on the right-hand side of the keyed entry.

-> Par d s b 

IMaps containing other LVars have some additional capabilities compared to those containing regular Haskell data. In particular, it is possible to modify existing entries (monotonically). Further, this modify function implicitly inserts a "bottom" element if there is no existing entry for the key.

Unfortunately, that means that this takes another computation for creating new "bottom" elements for the nested LVars stored inside the IMap.

Generic routines and convenient aliases

gmodifySource

Arguments

:: forall f a b d s key . (Ord key, LVarData1 f, LVarWBottom f, LVContents f a, Show key, Ord a) 
=> IMap key s (f s a) 
-> key

The key to lookup.

-> (f s a -> Par d s b)

The computation to apply on the right-hand side of the keyed entry.

-> Par d s b 

A generic version of modify that does not require a newBottom argument, rather, it uses the generic version of that function.

getOrInit :: forall f a b d s key. (Ord key, LVarData1 f, LVarWBottom f, LVContents f a, Show key, Ord a) => key -> IMap key s (f s a) -> Par d s (f s a)Source

Return the preexisting value for a key if it exists, and otherwise return

This is a convenience routine that can easily be defined in terms of gmodify

Iteration and callbacks

forEach :: IMap 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.

forEachHPSource

Arguments

:: Maybe HandlerPool

optional pool to enroll in

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

withCallbacksThenFreeze :: forall k v b s. Eq b => IMap k s v -> (k -> v -> QPar s ()) -> QPar s b -> QPar s bSource

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.

Quasi-deterministic operations

freezeMap :: IMap k s v -> QPar s (Map k v)Source

Get the exact contents of the map. As with any quasi-deterministic operation, using freezeMap may cause your program to exhibit a limited form of nondeterminism: it will never return the wrong answer, but it may include synchronization bugs that can (nondeterministically) cause exceptions.

This Data.Map-based implementation has the special property that you can retrieve the full map without any IO, and without nondeterminism leaking. (This is because the internal order is fixed for the tree-based representation of maps that Data.Map uses.)

fromIMap :: IMap k Frzn a -> Map k aSource

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

traverseFrzn_ :: Ord k => (k -> a -> Par d s ()) -> IMap k Frzn a -> Par d s ()Source

Traverse a frozen map for side effect. This is useful (in comparison with more generic operations) because the function passed in may see the key as well as the value.

Higher-level derived operations

copy :: (Ord k, Eq v) => IMap k s v -> Par d s (IMap k s v)Source

Return a fresh map which will contain strictly more elements than the input. That is, things put in the former go in the latter, but not vice versa.

traverseMap :: (Ord k, Eq b) => (k -> a -> Par d s b) -> IMap k s a -> Par d s (IMap k s b)Source

Establish a monotonic map between the input and output sets. Produce a new result based on each element, while leaving the keys the same.

traverseMap_ :: (Ord k, Eq b) => (k -> a -> Par d s b) -> IMap k s a -> IMap k s b -> Par d s ()Source

An imperative-style, in-place version of traverseMap that takes the output set as an argument.

union :: (Ord k, Eq a) => IMap k s a -> IMap k s a -> Par d s (IMap k s a)Source

Return a new map which will (ultimately) contain everything in either input map. Conflicting entries will result in a multiple put exception.

Alternate versions of derived ops that expose HandlerPools they create

traverseMapHP :: (Ord k, Eq b) => Maybe HandlerPool -> (k -> a -> Par d s b) -> IMap k s a -> Par d s (IMap k s b)Source

A variant of traverseMap that optionally ties the handlers to a pool.

traverseMapHP_ :: (Ord k, Eq b) => Maybe HandlerPool -> (k -> a -> Par d s b) -> IMap k s a -> IMap k s b -> Par d s ()Source

A variant of traverseMap_ that optionally ties the handlers to a pool.

unionHP :: (Ord k, Eq a) => Maybe HandlerPool -> IMap k s a -> IMap k s a -> Par d s (IMap k s a)Source

A variant of union that optionally ties the handlers in the resulting set to the same handler pool as those in the two input sets.