ghc-8.2.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

Hoopl.Dataflow

Synopsis

Documentation

data C :: * #

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

ShapeLifter O C 

Methods

singletonDG :: f -> n O C -> DG f n O C

fwdEntryFact :: NonLocal n => n O C -> f -> Fact O f

fwdEntryLabel :: NonLocal n => n O C -> MaybeC O [Label]

ftransfer :: FwdTransfer n f -> n O C -> f -> Fact C f

frewrite :: FwdRewrite m n f -> n O C -> f -> m (Maybe (Graph n O C, FwdRewrite m n f))

bwdEntryFact :: NonLocal n => DataflowLattice f -> n O C -> Fact O f -> f

btransfer :: BwdTransfer n f -> n O C -> Fact C f -> f

brewrite :: BwdRewrite m n f -> n O C -> Fact C f -> m (Maybe (Graph n O C, BwdRewrite m n f))

ShapeLifter C O 

Methods

singletonDG :: f -> n C O -> DG f n C O

fwdEntryFact :: NonLocal n => n C O -> f -> Fact C f

fwdEntryLabel :: NonLocal n => n C O -> MaybeC C [Label]

ftransfer :: FwdTransfer n f -> n C O -> f -> Fact O f

frewrite :: FwdRewrite m n f -> n C O -> f -> m (Maybe (Graph n C O, FwdRewrite m n f))

bwdEntryFact :: NonLocal n => DataflowLattice f -> n C O -> Fact C f -> f

btransfer :: BwdTransfer n f -> n C O -> Fact O f -> f

brewrite :: BwdRewrite m n f -> n C O -> Fact O f -> m (Maybe (Graph n C O, BwdRewrite m n f))

NonLocal n => LabelsPtr (n e C) 

Methods

targetLabels :: n e C -> [Label] #

type Fact C f 
type Fact C f = FactBase f
type IndexedCO C a _b 
type IndexedCO C a _b = a

data O :: * #

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

ShapeLifter O O 

Methods

singletonDG :: f -> n O O -> DG f n O O

fwdEntryFact :: NonLocal n => n O O -> f -> Fact O f

fwdEntryLabel :: NonLocal n => n O O -> MaybeC O [Label]

ftransfer :: FwdTransfer n f -> n O O -> f -> Fact O f

frewrite :: FwdRewrite m n f -> n O O -> f -> m (Maybe (Graph n O O, FwdRewrite m n f))

bwdEntryFact :: NonLocal n => DataflowLattice f -> n O O -> Fact O f -> f

btransfer :: BwdTransfer n f -> n O O -> Fact O f -> f

brewrite :: BwdRewrite m n f -> n O O -> Fact O f -> m (Maybe (Graph n O O, BwdRewrite m n f))

ShapeLifter O C 

Methods

singletonDG :: f -> n O C -> DG f n O C

fwdEntryFact :: NonLocal n => n O C -> f -> Fact O f

fwdEntryLabel :: NonLocal n => n O C -> MaybeC O [Label]

ftransfer :: FwdTransfer n f -> n O C -> f -> Fact C f

frewrite :: FwdRewrite m n f -> n O C -> f -> m (Maybe (Graph n O C, FwdRewrite m n f))

bwdEntryFact :: NonLocal n => DataflowLattice f -> n O C -> Fact O f -> f

btransfer :: BwdTransfer n f -> n O C -> Fact C f -> f

brewrite :: BwdRewrite m n f -> n O C -> Fact C f -> m (Maybe (Graph n O C, BwdRewrite m n f))

ShapeLifter C O 

Methods

singletonDG :: f -> n C O -> DG f n C O

fwdEntryFact :: NonLocal n => n C O -> f -> Fact C f

fwdEntryLabel :: NonLocal n => n C O -> MaybeC C [Label]

ftransfer :: FwdTransfer n f -> n C O -> f -> Fact O f

frewrite :: FwdRewrite m n f -> n C O -> f -> m (Maybe (Graph n C O, FwdRewrite m n f))

bwdEntryFact :: NonLocal n => DataflowLattice f -> n C O -> Fact C f -> f

btransfer :: BwdTransfer n f -> n C O -> Fact O f -> f

brewrite :: BwdRewrite m n f -> n C O -> Fact O f -> m (Maybe (Graph n C O, BwdRewrite m n f))

type Fact O f 
type Fact O f = f
type IndexedCO O _a b 
type IndexedCO O _a b = b

data Block (n :: * -> * -> *) e x :: (* -> * -> *) -> * -> * -> * #

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) 

Methods

entryLabel :: Block n C x -> Label #

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

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

entryLabel #

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.

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 family Fact x f :: * #

Instances

type Fact O f 
type Fact O f = f
type Fact C f 
type Fact C f = FactBase f

type FactBase f = LabelMap 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.