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

Safe HaskellTrustworthy

Data.LVar.SLMap

Contents

Description

This module provides finite maps that only grow. It is based on a concurrent skip list implementation of maps.

This module is usually a more efficient alternative to PureMap, and provides almost the same interface. However, it's always good to test multiple data structures if you have a performance-critical use case.

Synopsis

The type and its basic operations

data 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: this data structure reduces contention between parallel computations inserting into the map, but all blocking computations are not as scalable. All continuations waiting for not-yet-present elements will currently share a single queue [2013.09.26].

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 :: Ord k => Par d s (IMap k s v)Source

Create a fresh map with nothing in it.

newMap :: Ord k => 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

Create a new map drawing initial elements from an existing list.

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

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

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.

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

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

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

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.

Quasi-deterministic operations

freezeMap :: Ord k => IMap k s v -> QPar s (IMap k Frzn 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 is an O(1) operation that doesn't copy the in-memory representation of the IMap.

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.

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

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 map 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 map as an argument.

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

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

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

Return a new map which will (ultimately) contain everything in either input map. Conflicting entries will result in a multiple put exception. Optionally ties the handlers to a pool.

Debugging Helpers

levelCounts :: IMap k s a -> IO [Int]Source