Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
A graph representation of a sequence of Futhark statements
(i.e. a Body
), built to handle fusion. Could perhaps be made
more general. An important property is that it does not handle
"nested bodies" (e.g. Match
); these are represented as single
nodes.
This is all implemented on top of the graph representation provided
by the fgl
package (Data.Graph.Inductive). The graph provided
by this package allows nodes and edges to have arbitrarily-typed
"labels". It is these labels (EdgeT
, NodeT
) that we use to
contain Futhark-specific information. An edge goes *from*
consumers to producers. There are also edges that do not represent
normal data dependencies, but other things. This means that a node
can have multiple edges for the same name, indicating different
kinds of dependencies.
Synopsis
- data EdgeT
- data NodeT
- type DepContext = Context NodeT EdgeT
- type DepGraphAug m = DepGraph -> m DepGraph
- data DepGraph = DepGraph {
- dgGraph :: Gr NodeT EdgeT
- dgProducerMapping :: ProducerMapping
- dgAliasTable :: AliasTable
- type DepNode = LNode NodeT
- getName :: EdgeT -> VName
- nodeFromLNode :: DepNode -> Node
- mergedContext :: Ord b => a -> Context a b -> Context a b -> Context a b
- mapAcross :: Monad m => (DepContext -> m DepContext) -> DepGraphAug m
- edgesBetween :: DepGraph -> Node -> Node -> [DepEdge]
- reachable :: DepGraph -> Node -> Node -> Bool
- applyAugs :: Monad m => [DepGraphAug m] -> DepGraphAug m
- depsFromEdge :: DepEdge -> VName
- contractEdge :: Monad m => Node -> DepContext -> DepGraphAug m
- isRealNode :: NodeT -> Bool
- isCons :: EdgeT -> Bool
- isDep :: EdgeT -> Bool
- isInf :: (Node, Node, EdgeT) -> Bool
- mkDepGraph :: (HasScope SOACS m, Monad m) => Body SOACS -> m DepGraph
- mkDepGraphForFun :: FunDef SOACS -> DepGraph
- pprg :: DepGraph -> String
Data structure
Information associated with an edge in the graph.
Information associated with a node in the graph.
StmNode (Stm SOACS) | |
SoacNode ArrayTransforms (Pat Type) (SOAC SOACS) (StmAux (ExpDec SOACS)) | |
TransNode VName ArrayTransform VName | First |
ResNode VName | Node corresponding to a result of the entire computation
(i.e. the |
FreeNode VName | Node corresponding to a free variable. These are used to safely handle consumption, which also means we don't have to create a node for every free single variable. |
MatchNode (Stm SOACS) [(NodeT, [EdgeT])] | |
DoNode (Stm SOACS) [(NodeT, [EdgeT])] |
type DepGraphAug m = DepGraph -> m DepGraph Source #
A "graph augmentation" is a monadic action that modifies the graph.
A dependency graph. Edges go from *consumers* to *producers* (i.e. from usage to definition). That means the incoming edges of a node are the dependents of that node, and the outgoing edges are the dependencies of that node.
DepGraph | |
|
Queries
nodeFromLNode :: DepNode -> Node Source #
Get the underlying fgl
node.
mergedContext :: Ord b => a -> Context a b -> Context a b -> Context a b Source #
Merges two contexts.
mapAcross :: Monad m => (DepContext -> m DepContext) -> DepGraphAug m Source #
Monadically modify every node of the graph.
edgesBetween :: DepGraph -> Node -> Node -> [DepEdge] Source #
Find all the edges connecting the two nodes.
reachable :: DepGraph -> Node -> Node -> Bool Source #
reachable dg from to
is true if to
is reachable from from
.
applyAugs :: Monad m => [DepGraphAug m] -> DepGraphAug m Source #
Apply several graph augmentations in sequence.
depsFromEdge :: DepEdge -> VName Source #
Get the variable name that this edge refers to.
contractEdge :: Monad m => Node -> DepContext -> DepGraphAug m Source #
Remove the given node, and insert the DepContext
into the
graph, replacing any existing information about the node contained
in the DepContext
.
isRealNode :: NodeT -> Bool Source #
Does the node acutally represent something in the program? A "non-real" node represents things like fake nodes inserted to express ordering due to consumption.
Construction
mkDepGraph :: (HasScope SOACS m, Monad m) => Body SOACS -> m DepGraph Source #
Make a dependency graph corresponding to a Body
.