hoopl-3.7.8.0: A library to support dataflow analysis and optimization

Compiler.Hoopl

Synopsis

Documentation

type JoinFun a = OldFact a -> NewFact a -> (ChangeFlag, a)Source

newtype OldFact a Source

Constructors

OldFact a 

newtype NewFact a Source

Constructors

NewFact a 

data FwdPass n f Source

type FwdTransfer n f = forall e x. n e x -> Fact e f -> Fact x fSource

type FwdRewrite n f = forall e x. n e x -> Fact e f -> Maybe (FwdRes n f e x)Source

type SimpleFwdRewrite n f = forall e x. n e x -> Fact e f -> Maybe (AGraph n e x)Source

data FwdRes n f e x Source

Constructors

FwdRes (AGraph n e x) (FwdRewrite n f) 

data BwdPass n f Source

type BwdTransfer n f = forall e x. n e x -> Fact x f -> Fact e fSource

type BwdRewrite n f = forall e x. n e x -> Fact x f -> Maybe (BwdRes n f e x)Source

type SimpleBwdRewrite n f = forall e x. n e x -> Fact x f -> Maybe (AGraph n e x)Source

data BwdRes n f e x Source

Constructors

BwdRes (AGraph n e x) (BwdRewrite n f) 

type family Fact x f :: *Source

analyzeAndRewriteFwd :: forall n f. Edges n => FwdPass n f -> Body n -> FactBase f -> FuelMonad (Body n, FactBase f)Source

analyzeAndRewriteBwd :: forall n f. Edges n => BwdPass n f -> Body n -> FactBase f -> FuelMonad (Body n, FactBase f)Source

data FuelMonad a Source

Instances

data O Source

Instances

data C Source

Instances

data Block n e x whereSource

Constructors

BUnit :: n e x -> Block n e x 
BCat :: Block n e O -> Block n O x -> Block n e x 

Instances

Edges n => Edges (Block n) 

data Body n whereSource

Constructors

BodyEmpty :: Body n 
BodyUnit :: Block n C C -> Body n 
BodyCat :: Body n -> Body n -> Body n 

data Graph n e x whereSource

Constructors

GNil :: Graph n O O 
GUnit :: Block n O O -> Graph n O O 
GMany :: MaybeO e (Block n O C) -> Body n -> MaybeO x (Block n C O) -> Graph n e x 

data MaybeO ex t whereSource

Constructors

JustO :: t -> MaybeO O t 
NothingO :: MaybeO C t 

class Edges thing whereSource

Methods

entryLabel :: thing C x -> LabelSource

successors :: thing e C -> [Label]Source

Instances

Edges n => Edges (Block n) 

addBlock :: Block n C C -> Body n -> Body nSource

bodyList :: Edges n => Body n -> [(Label, Block n C C)]Source

data Label Source

Instances

type AGraph n e x = FuelMonad (Graph n e x)Source

(<*>) :: AGraph n e O -> AGraph n O x -> AGraph n e xSource

As noted in the paper, we can define a single, polymorphic type of splicing operation with the very polymorphic type AGraph n e a -> AGraph n a x -> AGraph n e x However, we feel that this operation is a bit too polymorphic, and that it's too easy for clients to use it blindly without thinking. We therfore split it into several operations:

  • The <*> operator is true concatenation, for connecting open graphs.
  • The operators addEntrySeq or addExitSeq allow a client to add an entry or exit sequence to a graph that is closed at the entry or exit.
  • The operator addBlocks adds a set of basic blocks (represented as a closed/closed AGraph to an existing graph, without changing the shape of the existing graph. In some cases, it's necessary to introduce a branch and a label to 'get around' the blocks added, so this operator, and other functions based on it, requires a HooplNode type-class constraint. (In GHC 6.12 this operator was called outOfLine.)
  • The operator unionBlocks takes the union of two sets of basic blocks, each of which is represented as a closed/closed AGraph. It is not redundant with addBlocks, because addBlocks requires a HooplNode constraint but unionBlocks does not.

There is some redundancy in this representation (any instance of addEntrySeq is also an instance of either addExitSeq or addBlocks), but because the different operators restrict polymorphism in different ways, we felt some redundancy would be appropriate.

addEntrySeq :: AGraph n O C -> AGraph n C x -> AGraph n O xSource

addExitSeq :: AGraph n e C -> AGraph n C O -> AGraph n e OSource

addBlocks :: HooplNode n => AGraph n e x -> AGraph n C C -> AGraph n e xSource

withFreshLabels :: Labels l => (l -> AGraph n e x) -> AGraph n e xSource

mkMiddles :: [n O O] -> AGraph n O OSource

mkLast :: n O C -> AGraph n O CSource

mkWhileDo :: HooplNode n => (Label -> Label -> AGraph n O C) -> AGraph n O O -> AGraph n O OSource

class IfThenElseable x whereSource

Methods

mkIfThenElse :: HooplNode n => (Label -> Label -> AGraph n O C) -> AGraph n O x -> AGraph n O x -> AGraph n O xSource

class Edges n => HooplNode n whereSource