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

Safe HaskellSafe
LanguageHaskell2010

Compiler.Hoopl.Internals

Contents

Synopsis

Shapes

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

IfThenElseable O 

Methods

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

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

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

IfThenElseable C 

Methods

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

NonLocal n => LabelsPtr (n e C) 

Methods

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

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

data MaybeO ex t where Source

Maybe type indexed by open/closed

Constructors

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

Instances

Functor (MaybeO ex) 

Methods

fmap :: (a -> b) -> MaybeO ex a -> MaybeO ex b Source

(<$) :: a -> MaybeO ex b -> MaybeO ex a Source

data MaybeC ex t where Source

Maybe type indexed by closed/open

Constructors

JustC :: t -> MaybeC C t 
NothingC :: MaybeC O t 

Instances

Functor (MaybeC ex) 

Methods

fmap :: (a -> b) -> MaybeC ex a -> MaybeC ex b Source

(<$) :: a -> MaybeC ex b -> MaybeC ex a Source

type family IndexedCO ex a b :: * Source

Either type indexed by closed/open using type families

Instances

type IndexedCO C a _b = a 
type IndexedCO O _a b = b 

data Shape ex where Source

Dynamic shape value

Constructors

Closed :: Shape C 
Open :: Shape O 

Blocks

data Block n e x where 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.

Constructors

BlockCO :: n C O -> Block n O O -> Block n C O 
BlockCC :: n C O -> Block n O O -> n O C -> Block n C C 
BlockOC :: Block n O O -> n O C -> Block n O C 
BNil :: Block n O O 
BMiddle :: n O O -> Block n O O 
BCat :: Block n O O -> Block n O O -> Block n O O 
BSnoc :: Block n O O -> n O O -> Block n O O 
BCons :: n O O -> Block n O O -> Block n O O 

Instances

NonLocal n => NonLocal (Block n) 

Methods

entryLabel :: Block n C x -> Label Source

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

Predicates on Blocks

Constructing blocks

blockCons :: n O O -> Block n O x -> Block n O x Source

blockSnoc :: Block n e O -> n O O -> Block n e O Source

blockJoinHead :: n C O -> Block n O x -> Block n C x Source

blockJoinTail :: Block n e O -> n O C -> Block n e C Source

blockJoin :: n C O -> Block n O O -> n O C -> Block n C C Source

blockJoinAny :: (MaybeC e (n C O), Block n O O, MaybeC x (n O C)) -> Block n e x Source

Convert a list of nodes to a block. The entry and exit node must or must not be present depending on the shape of the block.

blockAppend :: Block n e O -> Block n O x -> Block n e x Source

Deconstructing blocks

firstNode :: Block n C x -> n C O Source

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

endNodes :: Block n C C -> (n C O, n O C) Source

blockSplitHead :: Block n C x -> (n C O, Block n O x) Source

blockSplitTail :: Block n e C -> (Block n e O, n O C) Source

blockSplit :: Block n C C -> (n C O, Block n O O, n O C) Source

Split a closed block into its entry node, open middle block, and exit node.

blockSplitAny :: Block n e x -> (MaybeC e (n C O), Block n O O, MaybeC x (n O C)) Source

Modifying blocks

replaceFirstNode :: Block n C x -> n C O -> Block n C x Source

replaceLastNode :: Block n x C -> n O C -> Block n x C Source

Converting to and from lists

blockToList :: Block n O O -> [n O O] Source

Maps and folds

mapBlock :: (forall e x. n e x -> n' e x) -> Block n e x -> Block n' e x Source

map a function over the nodes of a Block

mapBlock' :: (forall e x. n e x -> n' e x) -> Block n e x -> Block n' e x Source

A strict mapBlock

mapBlock3' :: forall n n' e x. (n C O -> n' C O, n O O -> n' O O, n O C -> n' O C) -> Block n e x -> Block n' e x Source

map over a block, with different functions to apply to first nodes, middle nodes and last nodes respectively. The map is strict.

foldBlockNodesF :: forall n a. (forall e x. n e x -> a -> a) -> forall e x. Block n e x -> IndexedCO e a a -> IndexedCO x a a Source

foldBlockNodesF3 :: forall n a b c. (n C O -> a -> b, n O O -> b -> b, n O C -> b -> c) -> forall e x. Block n e x -> IndexedCO e a b -> IndexedCO x c b Source

Fold a function over every node in a block, forward or backward. The fold function must be polymorphic in the shape of the nodes.

foldBlockNodesB :: forall n a. (forall e x. n e x -> a -> a) -> forall e x. Block n e x -> IndexedCO x a a -> IndexedCO e a a Source

foldBlockNodesB3 :: forall n a b c. (n C O -> b -> c, n O O -> b -> b, n O C -> a -> b) -> forall e x. Block n e x -> IndexedCO x a b -> IndexedCO e c b Source

Biasing

frontBiasBlock :: Block n e x -> Block n e x Source

A block is "front biased" if the left child of every concatenation operation is a node, not a general block; a front-biased block is analogous to an ordinary list. If a block is front-biased, then its nodes can be traversed from front to back without general recusion; tail recursion suffices. Not all shapes can be front-biased; a closed/open block is inherently back-biased.

backBiasBlock :: Block n e x -> Block n e x Source

A block is "back biased" if the right child of every concatenation operation is a node, not a general block; a back-biased block is analogous to a snoc-list. If a block is back-biased, then its nodes can be traversed from back to back without general recusion; tail recursion suffices. Not all shapes can be back-biased; an open/closed block is inherently front-biased.

Body

type Body n = LabelMap (Block n C C) Source

A (possibly empty) collection of closed/closed blocks

type Body' block n = LabelMap (block n C C) Source

Body abstracted over block

bodyList :: Body' block n -> [(Label, block n C C)] Source

addBlock :: NonLocal thing => thing C C -> LabelMap (thing C C) -> LabelMap (thing C C) Source

bodyUnion :: forall a. LabelMap a -> LabelMap a -> LabelMap a Source

Graph

type Graph = Graph' Block Source

A control-flow graph, which may take any of four shapes (O/O, OC, CO, C/C). A graph open at the entry has a single, distinguished, anonymous entry point; if a graph is closed at the entry, its entry point(s) are supplied by a context.

data Graph' block n e x where Source

Graph' is abstracted over the block type, so that we can build graphs of annotated blocks for example (Compiler.Hoopl.Dataflow needs this).

Constructors

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

class NonLocal thing where Source

Gives access to the anchor points for nonlocal edges as well as the edges themselves

Minimal complete definition

entryLabel, successors

Methods

entryLabel :: thing C x -> Label Source

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

Instances

NonLocal n => NonLocal (Block n) 

Methods

entryLabel :: Block n C x -> Label Source

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

Constructing graphs

blockGraph :: NonLocal n => Block n e x -> Graph n e x Source

gUnitOO :: block n O O -> Graph' block n O O Source

gUnitOC :: block n O C -> Graph' block n O C Source

gUnitCO :: block n C O -> Graph' block n C O Source

gUnitCC :: NonLocal (block n) => block n C C -> Graph' block n C C Source

catGraphNodeOC :: NonLocal n => Graph n e O -> n O C -> Graph n e C Source

catGraphNodeOO :: Graph n e O -> n O O -> Graph n e O Source

catNodeCOGraph :: NonLocal n => n C O -> Graph n O x -> Graph n C x Source

catNodeOOGraph :: n O O -> Graph n O x -> Graph n O x Source

Splicing graphs

splice :: forall block n e a x. NonLocal (block n) => (forall e x. block n e O -> block n O x -> block n e x) -> Graph' block n e a -> Graph' block n a x -> Graph' block n e x Source

gSplice :: NonLocal n => Graph n e a -> Graph n a x -> Graph n e x Source

Maps

mapGraph :: (forall e x. n e x -> n' e x) -> Graph n e x -> Graph n' e x Source

Maps over all nodes in a graph.

mapGraphBlocks :: forall block n block' n' e x. (forall e x. block n e x -> block' n' e x) -> Graph' block n e x -> Graph' block' n' e x Source

Function mapGraphBlocks enables a change of representation of blocks, nodes, or both. It lifts a polymorphic block transform into a polymorphic graph transform. When the block representation stabilizes, a similar function should be provided for blocks.

Folds

foldGraphNodes :: forall n a. (forall e x. n e x -> a -> a) -> forall e x. Graph n e x -> a -> a Source

Fold a function over every node in a graph. The fold function must be polymorphic in the shape of the nodes.

Extracting Labels

labelsDefined :: forall block n e x. NonLocal (block n) => Graph' block n e x -> LabelSet Source

labelsUsed :: forall block n e x. NonLocal (block n) => Graph' block n e x -> LabelSet Source

Depth-first traversals

postorder_dfs :: NonLocal (block n) => Graph' block n O x -> [block n C C] Source

Traversal: postorder_dfs returns a list of blocks reachable from the entry of enterable graph. The entry and exit are *not* included. The list has the following property:

Say a "back reference" exists if one of a block's control-flow successors precedes it in the output list

Then there are as few back references as possible

The output is suitable for use in a forward dataflow problem. For a backward problem, simply reverse the list. (postorder_dfs is sufficiently tricky to implement that one doesn't want to try and maintain both forward and backward versions.)

postorder_dfs_from :: (NonLocal block, LabelsPtr b) => LabelMap (block C C) -> b -> [block C C] Source

postorder_dfs_from_except :: forall block e. (NonLocal block, LabelsPtr e) => LabelMap (block C C) -> e -> LabelSet -> [block C C] Source

preorder_dfs :: NonLocal (block n) => Graph' block n O x -> [block n C C] Source

preorder_dfs_from_except :: forall block e. (NonLocal block, LabelsPtr e) => LabelMap (block C C) -> e -> LabelSet -> [block C C] Source

class LabelsPtr l where Source

Minimal complete definition

targetLabels

Methods

targetLabels :: l -> [Label] Source

Instances

LabelsPtr LabelSet 
LabelsPtr Label 
LabelsPtr l => LabelsPtr [l] 

Methods

targetLabels :: [l] -> [Label] Source

NonLocal n => LabelsPtr (n e C) 

Methods

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

data LabelMap v Source

Instances

IsMap LabelMap 

Associated Types

type KeyOf (LabelMap :: TYPE Lifted -> TYPE Lifted) :: TYPE Lifted Source

Methods

mapNull :: LabelMap a -> Bool Source

mapSize :: LabelMap a -> Int Source

mapMember :: KeyOf LabelMap -> LabelMap a -> Bool Source

mapLookup :: KeyOf LabelMap -> LabelMap a -> Maybe a Source

mapFindWithDefault :: a -> KeyOf LabelMap -> LabelMap a -> a Source

mapEmpty :: LabelMap a Source

mapSingleton :: KeyOf LabelMap -> a -> LabelMap a Source

mapInsert :: KeyOf LabelMap -> a -> LabelMap a -> LabelMap a Source

mapInsertWith :: (a -> a -> a) -> KeyOf LabelMap -> a -> LabelMap a -> LabelMap a Source

mapDelete :: KeyOf LabelMap -> LabelMap a -> LabelMap a Source

mapUnion :: LabelMap a -> LabelMap a -> LabelMap a Source

mapUnionWithKey :: (KeyOf LabelMap -> a -> a -> a) -> LabelMap a -> LabelMap a -> LabelMap a Source

mapDifference :: LabelMap a -> LabelMap a -> LabelMap a Source

mapIntersection :: LabelMap a -> LabelMap a -> LabelMap a Source

mapIsSubmapOf :: Eq a => LabelMap a -> LabelMap a -> Bool Source

mapMap :: (a -> b) -> LabelMap a -> LabelMap b Source

mapMapWithKey :: (KeyOf LabelMap -> a -> b) -> LabelMap a -> LabelMap b Source

mapFold :: (a -> b -> b) -> b -> LabelMap a -> b Source

mapFoldWithKey :: (KeyOf LabelMap -> a -> b -> b) -> b -> LabelMap a -> b Source

mapFilter :: (a -> Bool) -> LabelMap a -> LabelMap a Source

mapElems :: LabelMap a -> [a] Source

mapKeys :: LabelMap a -> [KeyOf LabelMap] Source

mapToList :: LabelMap a -> [(KeyOf LabelMap, a)] Source

mapFromList :: [(KeyOf LabelMap, a)] -> LabelMap a Source

mapFromListWith :: (a -> a -> a) -> [(KeyOf LabelMap, a)] -> LabelMap a Source

Eq v => Eq (LabelMap v) 

Methods

(==) :: LabelMap v -> LabelMap v -> Bool

(/=) :: LabelMap v -> LabelMap v -> Bool

Ord v => Ord (LabelMap v) 

Methods

compare :: LabelMap v -> LabelMap v -> Ordering

(<) :: LabelMap v -> LabelMap v -> Bool

(<=) :: LabelMap v -> LabelMap v -> Bool

(>) :: LabelMap v -> LabelMap v -> Bool

(>=) :: LabelMap v -> LabelMap v -> Bool

max :: LabelMap v -> LabelMap v -> LabelMap v

min :: LabelMap v -> LabelMap v -> LabelMap v

Show v => Show (LabelMap v) 
type KeyOf LabelMap = Label 

data DataflowLattice a Source

A transfer function might want to use the logging flag to control debugging, as in for example, it updates just one element in a big finite map. We don't want Hoopl to show the whole fact, and only the transfer function knows exactly what changed.

Constructors

DataflowLattice 

Fields

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

newtype OldFact a Source

Constructors

OldFact a 

newtype NewFact a Source

Constructors

NewFact a 

type family Fact x f :: * Source

Instances

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

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

mkFactBase creates a FactBase from a list of (Label, fact) pairs. If the same label appears more than once, the relevant facts are joined.

data FwdPass m n f Source

Constructors

FwdPass 

newtype FwdTransfer n f Source

Constructors

FwdTransfer3 

Fields

mkFTransfer :: (forall e x. n e x -> f -> Fact x f) -> FwdTransfer n f Source

mkFTransfer3 :: (n C O -> f -> f) -> (n O O -> f -> f) -> (n O C -> f -> FactBase f) -> FwdTransfer n f Source

newtype FwdRewrite m n f Source

Constructors

FwdRewrite3 

Fields

mkFRewrite :: FuelMonad m => (forall e x. n e x -> f -> m (Maybe (Graph n e x))) -> FwdRewrite m n f Source

Functions passed to mkFRewrite should not be aware of the fuel supply. The result returned by mkFRewrite respects fuel.

mkFRewrite3 :: forall m n f. FuelMonad m => (n C O -> f -> m (Maybe (Graph n C O))) -> (n O O -> f -> m (Maybe (Graph n O O))) -> (n O C -> f -> m (Maybe (Graph n O C))) -> FwdRewrite m n f Source

Functions passed to mkFRewrite3 should not be aware of the fuel supply. The result returned by mkFRewrite3 respects fuel.

wrapFR Source

Arguments

:: (forall e x. (n e x -> f -> m (Maybe (Graph n e x, FwdRewrite m n f))) -> n' e x -> f' -> m' (Maybe (Graph n' e x, FwdRewrite m' n' f')))

This argument may assume that any function passed to it respects fuel, and it must return a result that respects fuel.

-> FwdRewrite m n f 
-> FwdRewrite m' n' f' 

wrapFR2 Source

Arguments

:: (forall e x. (n1 e x -> f1 -> m1 (Maybe (Graph n1 e x, FwdRewrite m1 n1 f1))) -> (n2 e x -> f2 -> m2 (Maybe (Graph n2 e x, FwdRewrite m2 n2 f2))) -> n3 e x -> f3 -> m3 (Maybe (Graph n3 e x, FwdRewrite m3 n3 f3)))

This argument may assume that any function passed to it respects fuel, and it must return a result that respects fuel.

-> FwdRewrite m1 n1 f1 
-> FwdRewrite m2 n2 f2 
-> FwdRewrite m3 n3 f3 

data BwdPass m n f Source

Constructors

BwdPass 

newtype BwdTransfer n f Source

Constructors

BwdTransfer3 

Fields

mkBTransfer :: (forall e x. n e x -> Fact x f -> f) -> BwdTransfer n f Source

mkBTransfer3 :: (n C O -> f -> f) -> (n O O -> f -> f) -> (n O C -> FactBase f -> f) -> BwdTransfer n f Source

wrapBR Source

Arguments

:: (forall e x. Shape x -> (n e x -> Fact x f -> m (Maybe (Graph n e x, BwdRewrite m n f))) -> n' e x -> Fact x f' -> m' (Maybe (Graph n' e x, BwdRewrite m' n' f')))

This argument may assume that any function passed to it respects fuel, and it must return a result that respects fuel.

-> BwdRewrite m n f 
-> BwdRewrite m' n' f' 

wrapBR2 Source

Arguments

:: (forall e x. Shape x -> (n1 e x -> Fact x f1 -> m1 (Maybe (Graph n1 e x, BwdRewrite m1 n1 f1))) -> (n2 e x -> Fact x f2 -> m2 (Maybe (Graph n2 e x, BwdRewrite m2 n2 f2))) -> n3 e x -> Fact x f3 -> m3 (Maybe (Graph n3 e x, BwdRewrite m3 n3 f3)))

This argument may assume that any function passed to it respects fuel, and it must return a result that respects fuel.

-> BwdRewrite m1 n1 f1 
-> BwdRewrite m2 n2 f2 
-> BwdRewrite m3 n3 f3 

newtype BwdRewrite m n f Source

Constructors

BwdRewrite3 

Fields

mkBRewrite :: FuelMonad m => (forall e x. n e x -> Fact x f -> m (Maybe (Graph n e x))) -> BwdRewrite m n f Source

Functions passed to mkBRewrite should not be aware of the fuel supply. The result returned by mkBRewrite respects fuel.

mkBRewrite3 :: forall m n f. FuelMonad m => (n C O -> f -> m (Maybe (Graph n C O))) -> (n O O -> f -> m (Maybe (Graph n O O))) -> (n O C -> FactBase f -> m (Maybe (Graph n O C))) -> BwdRewrite m n f Source

Functions passed to mkBRewrite3 should not be aware of the fuel supply. The result returned by mkBRewrite3 respects fuel.

analyzeAndRewriteFwd :: forall m n f e x entries. (CheckpointMonad m, NonLocal n, LabelsPtr entries) => FwdPass m n f -> MaybeC e entries -> Graph n e x -> Fact e f -> m (Graph n e x, FactBase f, MaybeO x f) Source

if the graph being analyzed is open at the entry, there must be no other entry point, or all goes horribly wrong...

analyzeAndRewriteBwd :: (CheckpointMonad m, NonLocal n, LabelsPtr entries) => BwdPass m n f -> MaybeC e entries -> Graph n e x -> Fact x f -> m (Graph n e x, FactBase f, MaybeO e f) Source

if the graph being analyzed is open at the exit, I don't quite understand the implications of possible other exits

Respecting Fuel