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

Safe HaskellNone

Language.Syntactic.Sharing.SimpleCodeMotion

Description

Simple code motion transformation performing common sub-expression elimination and variable hoisting. Note that the implementation is very inefficient.

The code is based on an implementation by Gergely Dévai.

Synopsis

Documentation

data PrjDict dom Source

Interface for projecting binding constructs

Constructors

PrjDict 

Fields

prjVariable :: forall sig. dom sig -> Maybe VarId
 
prjLambda :: forall sig. dom sig -> Maybe VarId
 

data InjDict dom a b Source

Interface for injecting binding constructs

Constructors

InjDict 

Fields

injVariable :: VarId -> dom (Full a)
 
injLambda :: VarId -> dom (b :-> Full (a -> b))
 
injLet :: dom (a :-> ((a -> b) :-> Full b))
 

type MkInjDict dom = forall a b. ASTF dom a -> ASTF dom b -> Maybe (InjDict dom a b)Source

A function that, if possible, returns an InjDict for sharing a specific sub-expression. The first argument is the expression to be shared, and the second argument the expression in which it will be shared.

This function makes the caller of codeMotion responsible for making sure that the necessary type constraints are fulfilled (otherwise Nothing is returned). It also makes it possible to transfer information, e.g. from the shared expression to the introduced variable.

codeMotionSource

Arguments

:: forall dom a . (ConstrainedBy dom Typeable, AlphaEq dom dom dom [(VarId, VarId)]) 
=> (forall c. ASTF dom c -> Bool)

Control wether a sub-expression can be hoisted over the given expression

-> PrjDict dom 
-> MkInjDict dom 
-> ASTF dom a 
-> State VarId (ASTF dom a) 

Perform common sub-expression elimination and variable hoisting

prjDictFO :: forall dom p pVar. PrjDict (FODomain dom p pVar)Source

A PrjDict implementation for FODomain

reifySmart :: forall dom p pVar a. (AlphaEq dom dom (FODomain dom p pVar) [(VarId, VarId)], Syntactic a, Domain a ~ HODomain dom p pVar, p :< Typeable) => (forall c. ASTF (FODomain dom p pVar) c -> Bool) -> MkInjDict (FODomain dom p pVar) -> a -> ASTF (FODomain dom p pVar) (Internal a)Source

Like reify but with common sub-expression elimination and variable hoisting

mkInjDictFO :: forall dom pVar. Let :<: dom => (forall a. ASTF (FODomain dom Typeable pVar) a -> Maybe (Dict (pVar a))) -> (forall b. ASTF (FODomain dom Typeable pVar) b -> Bool) -> MkInjDict (FODomain dom Typeable pVar)Source

An MkInjDict implementation for FODomain

The supplied function determines whether or not an expression can be shared by returning a witness that the type of the expression satisfies the predicate pVar.