syntactic-0.6: Generic abstract syntax, and utilities for embedded languages

Language.Syntactic.Features.Binding.PartialEval

Description

Partial evaluation

Synopsis

Documentation

type ConstFolder ctx dom = forall a. ASTF (Lambda ctx :+: (Variable ctx :+: dom)) a -> a -> ASTF (Lambda ctx :+: (Variable ctx :+: 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 Eval dom => PartialEval feature ctx dom whereSource

Partial evaluation

Methods

partEvalFeat :: Proxy ctx -> ConstFolder ctx dom -> feature a -> HList (AST (Lambda ctx :+: (Variable ctx :+: dom))) a -> Writer (Set VarId) (ASTF (Lambda ctx :+: (Variable ctx :+: dom)) (EvalResult a))Source

Partial evaluation of a feature. The (Set VarId) returned is the set of free variables of the expression. However, free variables are counted in a "lazy" sense: free variables from sub-expressions that are never evaluated may not be counted. (The instance for Conditional will throw away the free variables of the pruned branch when the condition is statically known. This is one reason why partial evaluation and free variable calculation have to be done simultaneously.)

Instances

((Sym ctx') :<: dom, PartialEval dom ctx dom) => PartialEval (Sym ctx') ctx dom 
((Literal ctx') :<: dom, PartialEval dom ctx dom) => PartialEval (Literal ctx') ctx dom 
((Condition ctx') :<: dom, PartialEval dom ctx dom) => PartialEval (Condition ctx') ctx dom 
((Select ctx') :<: dom, PartialEval dom ctx dom) => PartialEval (Select ctx') ctx dom 
((Tuple ctx') :<: dom, PartialEval dom ctx dom) => PartialEval (Tuple ctx') ctx dom 
PartialEval dom ctx dom => PartialEval (Lambda ctx) ctx dom 
PartialEval dom ctx dom => PartialEval (Variable ctx) ctx dom 
(PartialEval sub1 ctx dom, PartialEval sub2 ctx dom) => PartialEval (:+: sub1 sub2) ctx dom 
((Let ctxa ctxb) :<: dom, PartialEval dom ctx dom) => PartialEval (Let ctxa ctxb) ctx dom 

partialEvalM :: PartialEval dom ctx dom => Proxy ctx -> ConstFolder ctx dom -> ASTF (Lambda ctx :+: (Variable ctx :+: dom)) a -> Writer (Set VarId) (ASTF (Lambda ctx :+: (Variable ctx :+: dom)) a)Source

partialEval :: PartialEval dom ctx dom => Proxy ctx -> ConstFolder ctx dom -> ASTF (Lambda ctx :+: (Variable ctx :+: dom)) a -> ASTF (Lambda ctx :+: (Variable ctx :+: dom)) aSource

Partially evaluate an expression

partEvalFeatDefault :: (feature :<: dom, WitnessCons feature, PartialEval dom ctx dom) => Proxy ctx -> ConstFolder ctx dom -> feature a -> HList (AST (Lambda ctx :+: (Variable ctx :+: dom))) a -> Writer (Set VarId) (ASTF (Lambda ctx :+: (Variable ctx :+: dom)) (EvalResult a))Source

Convenient default implementation of partEvalFeat (uses evalLambda to evaluate)