feldspar-language-0.4.0.2: A functional embedded language for DSP and parallelism

Feldspar.DSL.Lambda

Description

A module for lambda expressions

Synopsis

Documentation

type Ident = StringSource

Unique identifier

data Lam expr role a whereSource

Extensible lambda expressions

Constructors

Variable :: Ident -> Lam expr role a 
Value :: a -> Lam expr role a 
Lambda :: (Typeable rb, Typeable b) => (Lam expr ra a -> Lam expr rb b) -> Lam expr (ra -> rb) (a -> b) 
:$: :: (Typeable ra, Typeable a) => Lam expr (ra -> rb) (a -> b) -> Lam expr ra a -> Lam expr rb b 
Let :: String -> Lam expr (ra -> (ra -> rb) -> rb) (a -> (a -> b) -> b) 
Inject :: expr role a -> Lam expr role a 

Instances

ExprShow expr => ExprShow (Lam expr) 
Eval expr => Eval (Lam expr) 
ExprEq expr => ExprEq (Lam expr) 
ExprEq expr => Eq (Lam expr role a) 
(Num a, Typeable a) => Num (Lam Val () a) 
ExprShow (Lam expr) => Show (Lam expr role a) 
EdgeInfo (Network edge node (In ()) a) 
Typeable a => MultiEdge (Network edge node (In ()) a) node edge 

let_Source

Arguments

:: (Typeable ra, Typeable a, Typeable rb, Typeable b) 
=> String

Preferred base name

-> Lam expr ra a 
-> (Lam expr ra a -> Lam expr rb b) 
-> Lam expr rb b 

Let binding

freshVarSource

Arguments

:: String

Base name

-> State Integer (Lam expr role a) 

exprEqLam :: ExprEq expr => Lam expr ra a -> Lam expr rb b -> State Integer BoolSource

shallowApply :: Lam expr (ra -> rb) (a -> b) -> Lam expr ra a -> Lam expr rb bSource

Shallow application. Function argument must be a Lambda.

isVar :: Lam expr role a -> BoolSource

isLet :: Lam expr role a -> BoolSource

viewInfix :: String -> Maybe StringSource

Parser for infix operators of the form (op)

exprShowAppSource

Arguments

:: ExprShow expr 
=> [String]

Missing arguments

-> Lam expr role a

Partially applied expression

-> State Integer String 

Shows a partially applied expression

exprShowLam :: ExprShow expr => Lam expr role a -> State Integer StringSource

lamToTreeAppSource

Arguments

:: ExprShow expr 
=> Forest String

Missing arguments

-> Lam expr role a

Partially applied expression

-> State Integer (Tree String) 

Converts a partially applied expression to a tree

lamToTree :: ExprShow expr => Lam expr role a -> State Integer (Tree String)Source

Converts a lambda expression to a tree

showLamTree :: ExprShow expr => Lam expr role a -> StringSource

Show a lambda expression as a tree

drawLambda :: ExprShow expr => Lam expr role a -> IO ()Source

Print a lambda expression as a tree