futhark-0.22.2: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.Optimise.Fusion.GraphRep

Description

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* uses of variables to the node that produces that variable. 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 structure

data EdgeT Source #

Information associated with an edge in the graph.

Instances

Instances details
Show EdgeT Source # 
Instance details

Defined in Futhark.Optimise.Fusion.GraphRep

Methods

showsPrec :: Int -> EdgeT -> ShowS #

show :: EdgeT -> String #

showList :: [EdgeT] -> ShowS #

Eq EdgeT Source # 
Instance details

Defined in Futhark.Optimise.Fusion.GraphRep

Methods

(==) :: EdgeT -> EdgeT -> Bool #

(/=) :: EdgeT -> EdgeT -> Bool #

Ord EdgeT Source # 
Instance details

Defined in Futhark.Optimise.Fusion.GraphRep

Methods

compare :: EdgeT -> EdgeT -> Ordering #

(<) :: EdgeT -> EdgeT -> Bool #

(<=) :: EdgeT -> EdgeT -> Bool #

(>) :: EdgeT -> EdgeT -> Bool #

(>=) :: EdgeT -> EdgeT -> Bool #

max :: EdgeT -> EdgeT -> EdgeT #

min :: EdgeT -> EdgeT -> EdgeT #

data NodeT Source #

Information associated with a node in the graph.

Constructors

StmNode (Stm SOACS) 
SoacNode ArrayTransforms (Pat Type) (SOAC SOACS) (StmAux (ExpDec SOACS)) 
ResNode VName

Node corresponding to a result of the entire computation (i.e. the Result of a body). Any node that is not transitively reachable from one of these can be considered dead.

FreeNode VName

Node corresponding to a free variable. Unclear whether we actually need these.

FinalNode (Stms SOACS) NodeT (Stms SOACS) 
MatchNode (Stm SOACS) [(NodeT, [EdgeT])] 
DoNode (Stm SOACS) [(NodeT, [EdgeT])] 

Instances

Instances details
Show NodeT Source # 
Instance details

Defined in Futhark.Optimise.Fusion.GraphRep

Methods

showsPrec :: Int -> NodeT -> ShowS #

show :: NodeT -> String #

showList :: [NodeT] -> ShowS #

Eq NodeT Source # 
Instance details

Defined in Futhark.Optimise.Fusion.GraphRep

Methods

(==) :: NodeT -> NodeT -> Bool #

(/=) :: NodeT -> NodeT -> Bool #

type DepContext = Context NodeT EdgeT Source #

A tuple with four parts: inbound links to the node, the node itself, the NodeT "label", and outbound links from the node. This type is used to modify the graph in mapAcross.

type DepGraphAug m = DepGraph -> m DepGraph Source #

A "graph augmentation" is a monadic action that modifies the graph.

data DepGraph Source #

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.

Constructors

DepGraph 

Fields

type DepNode = LNode NodeT Source #

A pair of a Node and the node label.

Queries

getName :: EdgeT -> VName Source #

The name that this edge depends on.

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.

isCons :: EdgeT -> Bool Source #

Is this a Cons edge?

isDep :: EdgeT -> Bool Source #

Is there a possibility of fusion?

isInf :: (Node, Node, EdgeT) -> Bool Source #

Is this an infusible edge?

Construction

mkDepGraph :: (HasScope SOACS m, Monad m) => Body SOACS -> m DepGraph Source #

Make a dependency graph corresponding to a Body.

pprg :: DepGraph -> String Source #

Prettyprint dependency graph.