Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- exploreGraph_seq :: forall d s k v. (Ord k, Eq v, Show k, Show v) => (k -> Par d s (Response (Par d s) k v)) -> (k -> Par d s v) -> k -> Par d s v
- data Response par key ans
- exploreGraph :: forall s k v. (Ord k, Eq v, Show k, Show v) => (k -> Par QuasiDet s [k]) -> NodeAction QuasiDet s k v -> k -> Par QuasiDet s v
- data NodeValue k v
- = FinalValue !v
- | Defer k
- type NodeAction d s k v = IsCycle -> k -> [(k, IsCycle, IVar s v)] -> Par d s (NodeValue k v)
- class Show t => ShortShow t where
- shortTwo :: (ShortShow t, ShortShow t1) => Int -> t -> t1 -> (String, String)
An idiom for fixed point computations
:: (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 | 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.
A parallel version
:: (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.
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.
FinalValue !v | |
Defer k |
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.