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

Language.Syntactic.Features.Symbol

Description

Simple symbols

Sym provides a simple way to make syntactic symbols for prototyping. However, note that Sym is quite unsafe as it only uses String to distinguish between different symbols. Also, Sym has a very free type that allows any number of arguments.

Synopsis

Documentation

data Sym ctx a whereSource

Constructors

Sym :: (ConsType a, Sat ctx (EvalResult a)) => String -> ConsEval a -> Sym ctx a 

Instances

WitnessSat (Sym ctx) 
WitnessCons (Sym ctx) 
ExprEq (Sym ctx) 
ToTree (Sym ctx) 
Render (Sym ctx) 
Eval (Sym ctx) 
((Sym ctx') :<: dom, PartialEval dom ctx dom) => PartialEval (Sym ctx') ctx dom 

witnessSatSym :: forall ctx dom a. (Sym ctx) :<: dom => Proxy ctx -> ASTF dom a -> Maybe (Witness' ctx a)Source

sym0 :: (Sat ctx a, (Sym ctx) :<: dom) => Proxy ctx -> String -> a -> ASTF dom aSource

A zero-argument symbol

sym1 :: (Typeable a, Sat ctx b, (Sym ctx) :<: dom) => Proxy ctx -> String -> (a -> b) -> ASTF dom a -> ASTF dom bSource

A one-argument symbol

sym2 :: (Typeable a, Typeable b, Sat ctx c, (Sym ctx) :<: dom) => Proxy ctx -> String -> (a -> b -> c) -> ASTF dom a -> ASTF dom b -> ASTF dom cSource

A two-argument symbol

sym3 :: (Typeable a, Typeable b, Typeable c, Sat ctx d, (Sym ctx) :<: dom) => Proxy ctx -> String -> (a -> b -> c -> d) -> ASTF dom a -> ASTF dom b -> ASTF dom c -> ASTF dom dSource

A three-argument symbol

sym4 :: (Typeable a, Typeable b, Typeable c, Typeable d, Sat ctx e, (Sym ctx) :<: dom) => Proxy ctx -> String -> (a -> b -> c -> d -> e) -> ASTF dom a -> ASTF dom b -> ASTF dom c -> ASTF dom d -> ASTF dom eSource

A four-argument symbol

prjSym :: (Sym ctx) :<: sup => Proxy ctx -> sup a -> Maybe (Sym ctx a)Source

Partial symbol projection with explicit context

class IsSymbol expr whereSource

Class of expressions that can be treated as symbols

Methods

toSym :: expr a -> Sym Poly aSource

Instances

exprEqSym :: IsSymbol expr => expr a -> expr b -> BoolSource

Default implementation of exprEq

exprHashSym :: IsSymbol expr => expr a -> HashSource

Default implementation of exprHash

renderPartSym :: IsSymbol expr => [String] -> expr a -> StringSource

Default implementation of renderPart

evaluateSym :: IsSymbol expr => expr a -> aSource

Default implementation of evaluate