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

Safe HaskellNone
LanguageHaskell2010

Hoopl.Dataflow

Synopsis

Documentation

data C Source #

Used at the type level to indicate a "closed" structure which supports control transfer only through the use of named labels---no "fallthrough" is permitted. The number of control-flow edges is unconstrained.

Instances
Outputable (Block CmmNode C C) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode C O) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode O C) Source # 
Instance details

Defined in PprCmm

type Fact C f Source # 
Instance details

Defined in Hoopl.Dataflow

type Fact C f = FactBase f
type IndexedCO C a _b Source # 
Instance details

Defined in Hoopl.Block

type IndexedCO C a _b = a

data O Source #

Used at the type level to indicate an "open" structure with a unique, unnamed control-flow edge flowing in or out. Fallthrough and concatenation are permitted at an open point.

Instances
Outputable (Block CmmNode C O) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode O C) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode O O) Source # 
Instance details

Defined in PprCmm

type Fact O f Source # 
Instance details

Defined in Hoopl.Dataflow

type Fact O f = f
type IndexedCO O _a b Source # 
Instance details

Defined in Hoopl.Block

type IndexedCO O _a b = b

data Block n e x Source #

A sequence of nodes. May be any of four shapes (OO, OC, CO, CC). Open at the entry means single entry, mutatis mutandis for exit. A closedclosed block is a basic/ block and can't be extended further. Clients should avoid manipulating blocks and should stick to either nodes or graphs.

Instances
NonLocal n => NonLocal (Block n) Source # 
Instance details

Defined in Hoopl.Graph

Methods

entryLabel :: Block n C x -> Label Source #

successors :: Block n e C -> [Label] Source #

Outputable (Block CmmNode C C) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode C O) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode O C) Source # 
Instance details

Defined in PprCmm

Outputable (Block CmmNode O O) Source # 
Instance details

Defined in PprCmm

Outputable (Graph CmmNode e x) Source # 
Instance details

Defined in PprCmm

Methods

ppr :: Graph CmmNode e x -> SDoc #

pprPrec :: Rational -> Graph CmmNode e x -> SDoc #

lastNode :: Block n x C -> n O C Source #

entryLabel Source #

Arguments

:: NonLocal thing 
=> thing C x 
-> Label

The label of a first node or block

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 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 f :: * Source #

Instances
type Fact C f Source # 
Instance details

Defined in Hoopl.Dataflow

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

Defined in Hoopl.Dataflow

type Fact O f = f

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

Returns the joined facts for each label.

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.