Safe Haskell | None |
---|
Basic optimization
- type ConstFolder dom = forall a. ASTF dom a -> a -> ASTF dom a
- class Optimize sym where
- type Optimize' dom = (Optimize dom, EvalBind dom, AlphaEq dom dom dom [(VarId, VarId)], ConstrainedBy dom Typeable)
- optimizeM :: Optimize' dom => ConstFolder dom -> ASTF dom a -> Writer (Set VarId) (ASTF dom a)
- optimize :: Optimize' dom => ConstFolder dom -> ASTF dom a -> ASTF dom a
- optimizeSymDefault :: Optimize' dom => ConstFolder dom -> (sym sig -> AST dom sig) -> sym sig -> Args (AST dom) sig -> Writer (Set VarId) (ASTF dom (DenResult sig))
Documentation
type ConstFolder dom = forall a. ASTF dom a -> a -> ASTF dom aSource
Constant folder
Given an expression and the statically known value of that expression,
returns a (possibly) new expression with the same meaning as the original.
Typically, the result will be a Literal
, if the relevant type constraints
are satisfied.
class Optimize sym whereSource
Basic optimization
optimizeSym :: Optimize' dom => ConstFolder dom -> (sym sig -> AST dom sig) -> sym sig -> Args (AST dom) sig -> Writer (Set VarId) (ASTF dom (DenResult sig))Source
Bottom-up optimization of an expression. The optimization performed is
up to each instance, but the intention is to provide a sensible set of
"always-appropriate" optimizations. The default implementation
optimizeSymDefault
does only constant folding. This constant folding
uses the set of free variables to know when it's static evaluation is
possible. Thus it is possible to help constant folding of other
constructs by pruning away parts of the syntax tree that are known not to
be needed. For example, by replacing (using ordinary Haskell as an
example)
if True then a else b
with a
, we don't need to report the free variables in b
. This, in
turn, can lead to more constant folding higher up in the expression.
Optimize Empty | |
Optimize Condition | |
Optimize Construct | |
Optimize Identity | |
Optimize Literal | |
Optimize Tuple | |
Optimize Select | |
Optimize Let | |
Optimize Lambda | |
Optimize Variable | |
(Optimize sub1, Optimize sub2) => Optimize (:+: sub1 sub2) | |
Optimize dom => Optimize (:|| dom p) | |
Optimize dom => Optimize (:| dom p) | |
Optimize dom => Optimize (SubConstr1 c dom p) | |
Optimize dom => Optimize (SubConstr2 c dom pa pb) |
type Optimize' dom = (Optimize dom, EvalBind dom, AlphaEq dom dom dom [(VarId, VarId)], ConstrainedBy dom Typeable)Source
optimizeM :: Optimize' dom => ConstFolder dom -> ASTF dom a -> Writer (Set VarId) (ASTF dom a)Source
optimize :: Optimize' dom => ConstFolder dom -> ASTF dom a -> ASTF dom aSource
Optimize an expression
optimizeSymDefault :: Optimize' dom => ConstFolder dom -> (sym sig -> AST dom sig) -> sym sig -> Args (AST dom) sig -> Writer (Set VarId) (ASTF dom (DenResult sig))Source
Convenient default implementation of optimizeSym
(uses evalBind
to
partially evaluate)