fortran-src-0.1.0.3: Parser and anlyses for Fortran standards 66, 77, 90.

Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Analysis.DataFlow

Description

Dataflow analysis to be applied once basic block analysis is complete.

Synopsis

Documentation

dominators :: BBGr a -> DomMap Source #

Compute dominators of each bblock in the graph. Node A dominates node B when all paths from the start node (0) must pass through node A in order to reach node B. That will be represented as the relation (B, [A, ...]) in the DomMap.

iDominators :: BBGr a -> IDomMap Source #

Compute the immediate dominator of each bblock in the graph. The immediate dominator is, in a sense, the closest dominator of a node. Given nodes A and B, you can say that node A is immediately dominated by node B if there does not exist any node C such that: node A dominates node C and node C dominates node B.

type DomMap = IntMap IntSet Source #

DomMap : node -> dominators of node

type IDomMap = IntMap Int Source #

IDomMap : node -> immediate dominator of node

postOrder :: OrderF a Source #

The postordering of a graph outputs the label after traversal of children.

revPostOrder :: OrderF a Source #

Reversed postordering.

preOrder :: OrderF a Source #

The preordering of a graph outputs the label before traversal of children.

revPreOrder :: OrderF a Source #

Reversed preordering.

type OrderF a = BBGr a -> [Node] Source #

An OrderF is a function from graph to a specific ordering of nodes.

dataFlowSolver Source #

Arguments

:: Ord t 
=> BBGr a

basic block graph

-> (Node -> InOut t)

initialisation for in and out dataflows

-> OrderF a

ordering function

-> (OutF t -> InF t)

compute the in-flow given an out-flow function

-> (InF t -> OutF t)

compute the out-flow given an in-flow function

-> InOutMap t

final dataflow for each node

Apply the iterative dataflow analysis method.

showDataFlow :: (Data a, Out a, Show a) => ProgramFile (Analysis a) -> String Source #

Show some information about dataflow analyses.

type InOut t = (t, t) Source #

InOut : (dataflow into the bblock, dataflow out of the bblock)

type InOutMap t = IntMap (InOut t) Source #

InOutMap : node -> (dataflow into node, dataflow out of node)

type InF t = Node -> t Source #

InF, a function that returns the in-dataflow for a given node

type OutF t = Node -> t Source #

OutF, a function that returns the out-dataflow for a given node

liveVariableAnalysis :: Data a => BBGr (Analysis a) -> InOutMap (Set Name) Source #

Dataflow analysis for live variables given basic block graph. Muchnick, p. 445: A variable is "live" at a particular program point if there is a path to the exit along which its value may be used before it is redefined. It is "dead" if there is no such path.

reachingDefinitions :: Data a => DefMap -> BBGr (Analysis a) -> InOutMap IntSet Source #

Reaching definitions dataflow analysis. Reaching definitions are the set of variable-defining AST-block labels that may reach a program point. Suppose AST-block with label A defines a variable named v. Label A may reach another program point labeled P if there is at least one program path from label A to label P that does not redefine variable v.

genUDMap :: Data a => BlockMap a -> DefMap -> BBGr (Analysis a) -> InOutMap IntSet -> UDMap Source #

use-def map: map AST-block labels of variable-using AST-blocks to the AST-blocks that define those variables.

genDUMap :: Data a => BlockMap a -> DefMap -> BBGr (Analysis a) -> InOutMap IntSet -> DUMap Source #

def-use map: map AST-block labels of defining AST-blocks to the AST-blocks that may use the definition.

duMapToUdMap :: DUMap -> UDMap Source #

Invert the DUMap into a UDMap

type UDMap = IntMap IntSet Source #

UDMap : use -> { definition }

type DUMap = IntMap IntSet Source #

DUMap : definition -> { use }

genFlowsToGraph Source #

Arguments

:: Data a 
=> BlockMap a 
-> DefMap 
-> BBGr (Analysis a) 
-> InOutMap IntSet

result of reaching definitions

-> FlowsGraph a 

Flows-To analysis. Represent def-use map as a graph.

type FlowsGraph a = Gr (Block (Analysis a)) () Source #

FlowsGraph : nodes as AST-block (numbered by label), edges showing which definitions contribute to which uses.

genVarFlowsToMap :: Data a => DefMap -> FlowsGraph a -> VarFlowsMap Source #

Create a map (A -> Bs) where A "flows" or contributes towards the variables Bs.

type VarFlowsMap = Map Name (Set Name) Source #

Represent "flows" between variables

genBlockMap :: Data a => ProgramFile (Analysis a) -> BlockMap a Source #

Build a BlockMap from the AST. This can only be performed after analyseBasicBlocks has operated, created basic blocks, and labeled all of the AST-blocks with unique numbers.

genDefMap :: Data a => BlockMap a -> DefMap Source #

Build a DefMap from the BlockMap. This allows us to quickly look up the AST-block labels that wrote into the given variable.

type BlockMap a = IntMap (Block (Analysis a)) Source #

BlockMap : AST-block label -> AST-block Each AST-block has been given a unique number label during analysis of basic blocks. The purpose of this map is to provide the ability to lookup AST-blocks by label.

type DefMap = Map Name IntSet Source #

DefMap : variable name -> { AST-block label }

genCallMap :: Data a => ProgramFile (Analysis a) -> CallMap Source #

Create a call map showing the structure of the program.

type CallMap = Map ProgramUnitName (Set Name) Source #

CallMap : program unit name -> { name of function or subroutine }

loopNodes :: Graph gr => BackEdgeMap -> gr a b -> [IntSet] Source #

For each loop in the program, find out which bblock nodes are part of the loop by looking through the backedges (m, n) where n is considered the 'loop-header', delete n from the map, and then do a reverse-depth-first traversal starting from m to find all the nodes of interest. Intersect this with the strongly-connected component containing m, in case of improper graphs with weird control transfers.

genBackEdgeMap :: Graph gr => DomMap -> gr a b -> BackEdgeMap Source #

Find the edges that 'loop back' in the graph; ones where the target node dominates the source node. If the backedges are viewed as (m -> n) then n is considered the 'loop-header'

sccWith :: Graph gr => Node -> gr a b -> [Node] Source #

The strongly connected component containing a given node.

type BackEdgeMap = IntMap Node Source #

BackEdgeMap : node -> node

genLoopNodeMap :: Graph gr => BackEdgeMap -> gr a b -> LoopNodeMap Source #

Similar to loopNodes except it creates a map from loop-header to the set of loop nodes, for each loop-header.

type LoopNodeMap = IntMap IntSet Source #

LoopNodeMap : node -> { node }

genInductionVarMap :: Data a => BackEdgeMap -> BBGr (Analysis a) -> InductionVarMap Source #

For each loop in the program, figure out the names of the induction variables: the variables that are used to represent the current iteration of the loop.

type InductionVarMap = IntMap (Set Name) Source #

Map of loop header nodes to the induction variables within that loop.

genInductionVarMapByASTBlock :: forall a. Data a => BackEdgeMap -> BBGr (Analysis a) -> InductionVarMapByASTBlock Source #

Generate an induction variable map that is indexed by the labels on AST-blocks within those loops.

type InductionVarMapByASTBlock = IntMap (Set Name) Source #

InductionVarMapByASTBlock : AST-block label -> { name }

noPredNodes :: Graph g => g a b -> [Node] Source #

Compute the set of nodes with no predecessors.