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

Safe HaskellNone
LanguageHaskell98

Data.LVar.CycGraph

Contents

Description

In contrast with Data.LVar.Memo, this module provides a way to run a computation for each node of a graph WITH support for cycles. Cycles are explicitly recognized and then may be handled in an application specific fashion.

Synopsis

An idiom for fixed point computations

exploreGraph_seq Source

Arguments

:: (Ord k, Eq v, Show k, Show v) 
=> (k -> Par d s (Response (Par d s) k v))

The computation to perform for new requests

-> (k -> Par d s v)

Handler for a cycle on k. The value it returns is in lieu of running the main computation at this particular node in the graph.

-> k

Key to lookup.

-> Par d s v 

This supercombinator does a parallel depth-first search of a dynamic graph, with detection of cycles.

Each node in the graph is a computation whose input is the key (the vertex ID). Each such computation dynamically computes which other keys it depends on and requests the values associated with those keys.

This implementation uses a sequential depth-first-search (DFS), starting from the initially requested key. One can picture this search as a directed tree radiating from the starting key. When a cycle is detected at any leaf of this tree, an alternate cycle handler is called instead of running the normal computation for that key.

data Response par key ans Source

A means of building a dynamic graph. The node computation returns a response which may either be a final value, or a request to explore more nodes (together with a continuation for the resulting value).

Note that because only one key is requested at a time, this cannot express parallel graph traversals.

Constructors

Done !ans 
Request !key (RequestCont par key ans) 

A parallel version

exploreGraph Source

Arguments

:: (Ord k, Eq v, Show k, Show v) 
=> (k -> Par QuasiDet s [k])

Sketch the graph: map a key onto its children.

-> NodeAction QuasiDet s k v

The computation to run at each graph node.

-> k

The initial node (key) from which to explore.

-> Par QuasiDet s v 

This combinator provides parallel exploration of a graph that contains cycles. The limitation is that the work to be performed at each node (NodeAction) is not invoked until the graph is fully traversed, i.e. after a barrier. Thus the graph explored is not a "dynamic graph" in the sense of being computed on the fly by the NodeAction.

The algorithm used in this function is fairly expensive. For each node, it uses a monotonic data structure to track the full set of other nodes that can reach it in the graph.

data NodeValue k v Source

At the end of the handler execution, the value of a node is either ready, or it is instead deferred to be exactly the value provided by another key.

Constructors

FinalValue !v 
Defer k 

Instances

(Eq k, Eq v) => Eq (NodeValue k v) 
(Ord k, Ord v) => Ord (NodeValue k v) 
(Show k, Show v) => Show (NodeValue k v) 

type NodeAction d s k v = IsCycle -> k -> [(k, IsCycle, IVar s v)] -> Par d s (NodeValue k v) Source

The handler at a particular node (key) in the graph. This takes as argument a key, along with a boolean indicating whether the current node has been found to be part of a cycle.

Also, for each child node, this handler is provided a way to demand the resulting value of that child node, plus an indication of whether the child node participates in a cycle.

Finally, this handler is expected to produce a value which becomes associated with the key.

Debugging aides

class Show t => ShortShow t where Source

A show class that tries to stay under a budget.

Minimal complete definition

Nothing

Methods

shortShow :: Int -> t -> String Source

shortTwo :: (ShortShow t, ShortShow t1) => Int -> t -> t1 -> (String, String) Source

Combine two things within a given size budget.