ghc-lib-0.20190204: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

CFG

Synopsis

Documentation

type CFG = EdgeInfoMap EdgeInfo Source #

A control flow graph where edges have been annotated with a weight.

data CfgEdge Source #

Constructors

CfgEdge 
Instances
Eq CfgEdge Source #

Careful! Since we assume there is at most one edge from A to B the Eq instance does not consider weight.

Instance details

Defined in CFG

Methods

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

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

Ord CfgEdge Source #

Edges are sorted ascending pointwise by weight, source and destination

Instance details

Defined in CFG

Outputable CfgEdge Source # 
Instance details

Defined in CFG

data EdgeInfo Source #

Information about edges

Instances
Eq EdgeInfo Source # 
Instance details

Defined in CFG

Outputable EdgeInfo Source # 
Instance details

Defined in CFG

newtype EdgeWeight Source #

Constructors

EdgeWeight Int 
Instances
Enum EdgeWeight Source # 
Instance details

Defined in CFG

Eq EdgeWeight Source # 
Instance details

Defined in CFG

Integral EdgeWeight Source # 
Instance details

Defined in CFG

Num EdgeWeight Source # 
Instance details

Defined in CFG

Ord EdgeWeight Source # 
Instance details

Defined in CFG

Real EdgeWeight Source # 
Instance details

Defined in CFG

Outputable EdgeWeight Source # 
Instance details

Defined in CFG

data TransitionSource Source #

Can we trace back a edge to a specific Cmm Node or has it been introduced for codegen. We use this to maintain some information which would otherwise be lost during the Cmm - asm transition. See also Note [Inverting Conditional Branches]

Constructors

CmmSource (CmmNode O C) 
AsmCodeGen 
Instances
Eq TransitionSource Source # 
Instance details

Defined in CFG

addWeightEdge :: BlockId -> BlockId -> EdgeWeight -> CFG -> CFG Source #

Adds a edge with the given weight to the cfg If there already existed an edge it is overwritten. `addWeightEdge from to weight cfg`

addEdge :: BlockId -> BlockId -> EdgeInfo -> CFG -> CFG Source #

Adds a new edge, overwrites existing edges if present

addNodesBetween :: CFG -> [(BlockId, BlockId, BlockId)] -> CFG Source #

Insert a block in the control flow between two other blocks. We pass a list of tuples (A,B,C) where * A -> C: Old edge * A -> B -> C : New Arc, where B is the new block. It's possible that a block has two jumps to the same block in the assembly code. However we still only store a single edge for these cases. We assign the old edge info to the edge A -> B and assign B -> C the weight of an unconditional jump.

filterEdges :: (BlockId -> BlockId -> EdgeInfo -> Bool) -> CFG -> CFG Source #

Filter the CFG with a custom function f. Paramaeters are `f from to edgeInfo`

addImmediateSuccessor :: BlockId -> BlockId -> CFG -> CFG Source #

Sometimes we insert a block which should unconditionally be executed after a given block. This function updates the CFG for these cases. So we get A -> B => A -> A' -> B -- -> C => -> C

mkWeightInfo :: Integral n => n -> EdgeInfo Source #

Convenience function, generate edge info based on weight not originating from cmm.

adjustEdgeWeight :: CFG -> (EdgeWeight -> EdgeWeight) -> BlockId -> BlockId -> CFG Source #

Adjust the weight between the blocks using the given function. If there is no such edge returns the original map.

infoEdgeList :: CFG -> [CfgEdge] Source #

Returns a unordered list of all edges with info

edgeList :: CFG -> [Edge] Source #

Returns a unordered list of all edges without weights

getSuccessorEdges :: CFG -> BlockId -> [(BlockId, EdgeInfo)] Source #

Get successors of a given node with edge weights.

getSuccessors :: CFG -> BlockId -> [BlockId] Source #

Get successors of a given node without edge weights.

getSuccEdgesSorted :: CFG -> BlockId -> [(BlockId, EdgeInfo)] Source #

Destinations from bid ordered by weight (descending)

weightedEdgeList :: CFG -> [(BlockId, BlockId, EdgeWeight)] Source #

Unordered list of edges with weight as Tuple (from,to,weight)

getCfgProc :: CfgWeights -> RawCmmDecl -> CFG Source #

Generate weights for a Cmm proc based on some simple heuristics.

sanityCheckCfg :: CFG -> LabelSet -> SDoc -> Bool Source #

Check if the nodes in the cfg and the set of blocks are the same. In a case of a missmatch we panic and show the difference.