ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Cmm.Dataflow

Synopsis

Documentation

type C = 'Closed #

type O = 'Open #

data Block (n :: Extensibility -> Extensibility -> Type) (e :: Extensibility) (x :: Extensibility) #

Instances

Instances details
OutputableP Platform (Block CmmNode C C) 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Block CmmNode C C -> SDoc

OutputableP Platform (Block CmmNode C O) 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Block CmmNode C O -> SDoc

OutputableP Platform (Block CmmNode O C) 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Block CmmNode O C -> SDoc

OutputableP Platform (Block CmmNode O O) 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Block CmmNode O O -> SDoc

OutputableP Platform (Graph CmmNode e x) 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Graph CmmNode e x -> SDoc

NonLocal n => NonLocal (Block n) 
Instance details

Defined in GHC.Cmm.Dataflow.Graph

Methods

entryLabel :: forall (x :: Extensibility). Block n C x -> Label #

successors :: forall (e :: Extensibility). Block n e C -> [Label]

lastNode :: forall n (x :: Extensibility). Block n x C -> n O C #

entryLabel :: forall (x :: Extensibility). NonLocal thing => thing C x -> Label #

foldNodesBwdOO :: (CmmNode O O -> f -> f) -> Block CmmNode O O -> f -> f Source #

Folds backward over all nodes of an open-open block. Strict in the accumulator.

foldRewriteNodesBwdOO :: forall f. (CmmNode O O -> f -> UniqSM (Block CmmNode O O, f)) -> Block CmmNode O O -> f -> UniqSM (Block CmmNode O O, f) Source #

Folds backward over all the nodes of an open-open block and allows rewriting them. The accumulator is both the block of nodes and f (usually dataflow facts). Strict in both accumulated parts.

data DataflowLattice a Source #

Constructors

DataflowLattice 

Fields

newtype OldFact a Source #

Constructors

OldFact a 

newtype NewFact a Source #

Constructors

NewFact a 

data JoinedFact a Source #

The result of joining OldFact and NewFact.

Constructors

Changed !a

Result is different than OldFact.

NotChanged !a

Result is the same as OldFact.

type TransferFun f = CmmBlock -> FactBase f -> FactBase f Source #

type RewriteFun f = CmmBlock -> FactBase f -> UniqSM (CmmBlock, FactBase f) Source #

Function for rewrtiting and analysis combined. To be used with rewriteCmm.

Currently set to work with UniqSM monad, but we could probably abstract that away (if we do that, we might want to specialize the fixpoint algorithms to the particular monads through SPECIALIZE).

type family Fact (x :: Extensibility) f :: Type Source #

Instances

Instances details
type Fact C f Source # 
Instance details

Defined in GHC.Cmm.Dataflow

type Fact C f = FactBase f
type Fact O f Source # 
Instance details

Defined in GHC.Cmm.Dataflow

type Fact O f = f

type FactBase f = LabelMap f #

getFact :: DataflowLattice f -> Label -> FactBase f -> f Source #

mkFactBase :: DataflowLattice f -> [(Label, f)] -> FactBase f Source #

Returns the joined facts for each label.

rewriteCmmBwd :: DataflowLattice f -> RewriteFun f -> CmmGraph -> FactBase f -> UniqSM (CmmGraph, FactBase f) Source #

joinOutFacts :: NonLocal n => DataflowLattice f -> n e C -> FactBase f -> f Source #

Returns the result of joining the facts from all the successors of the provided node or block.