Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generic representation of typed syntax trees
For details, see: A Generic Abstract Syntax Model for Embedded Languages (ICFP 2012, http://www.cse.chalmers.se/~emax/documents/axelsson2012generic.pdf).
Synopsis
- data AST dom sig where
- type ASTF dom a = AST dom (Full a)
- newtype Full a = Full {
- result :: a
- newtype a :-> sig = Partial (a -> sig)
- size :: AST dom sig -> Int
- class ApplySym sig f dom | sig dom -> f, f -> sig dom where
- type family DenResult sig
- data (dom1 :+: dom2) a where
- class Project sub sup where
- class Project sub sup => sub :<: sup where
- appSym :: (ApplySym sig f dom, sym :<: AST dom) => sym sig -> f
- symType :: P sym -> sym sig -> sym sig
- prjP :: Project sub sup => P sub -> sup sig -> Maybe (sub sig)
Syntax trees
data AST dom sig where Source #
Generic abstract syntax tree, parameterized by a symbol domain
(
represents a partially applied (or unapplied)
symbol, missing at least one argument, while AST
dom (a :->
b))(
represents a fully applied symbol, i.e. a complete syntax tree.AST
dom (Full
a))
Sym :: dom sig -> AST dom sig | |
(:$) :: AST dom (a :-> sig) -> AST dom (Full a) -> AST dom sig infixl 1 |
Instances
Signature of a fully applied symbol
Instances
Functor Full Source # | |
Eq a => Eq (Full a) Source # | |
Show a => Show (Full a) Source # | |
ApplySym (Full a) (ASTF dom a) dom Source # | |
Render dom => Show (ASTF dom a) # | |
Syntactic (ASTF dom a) Source # | |
(Syntactic a, Domain a ~ dom, ia ~ Internal a, SyntacticN b ib) => SyntacticN (a -> b) (AST dom (Full ia) -> ib) Source # | |
ApplySym sig f dom => ApplySym (a :-> sig) (ASTF dom a -> f) dom Source # | |
type DenResult (Full a) Source # | |
Defined in Language.Syntactic.Syntax | |
type Denotation (Full a) Source # | |
Defined in Language.Syntactic.Interpretation.Semantics | |
type Domain (ASTF dom a) Source # | |
Defined in Language.Syntactic.Sugar | |
type Internal (ASTF dom a) Source # | |
Defined in Language.Syntactic.Sugar |
newtype a :-> sig infixr 9 Source #
Signature of a partially applied (or unapplied) symbol
Partial (a -> sig) |
class ApplySym sig f dom | sig dom -> f, f -> sig dom where Source #
Class for the type-level recursion needed by appSym
Symbol domains
data (dom1 :+: dom2) a where infixr 9 Source #
Direct sum of two symbol domains
Instances
class Project sub sup where Source #
Symbol projection
Instances
Project expr expr Source # | |
Defined in Language.Syntactic.Syntax | |
Project sub sup => Project sub (AST sup) Source # | |
Project expr1 expr3 => Project expr1 (expr2 :+: expr3) Source # | |
Project expr1 (expr1 :+: expr2) Source # | |
Project sub sup => Project sub (sup :|| pred) Source # | |
Project sub sup => Project sub (sup :| pred) Source # | |
Project sub sup => Project sub (Decor info sup) Source # | |
Project sub sup => Project sub (SubConstr1 c sup p) Source # | |
Defined in Language.Syntactic.Constraint prj :: SubConstr1 c sup p a -> Maybe (sub a) Source # | |
Project sub sup => Project sub (SubConstr2 c sup pa pb) Source # | |
Defined in Language.Syntactic.Constraint prj :: SubConstr2 c sup pa pb a -> Maybe (sub a) Source # |
class Project sub sup => sub :<: sup where Source #
Symbol subsumption
Instances
expr :<: expr Source # | |
Defined in Language.Syntactic.Syntax | |
sub :<: sup => sub :<: (AST sup) Source # | |
Defined in Language.Syntactic.Syntax | |
expr1 :<: expr3 => expr1 :<: (expr2 :+: expr3) Source # | |
Defined in Language.Syntactic.Syntax | |
expr1 :<: (expr1 :+: expr2) Source # | |
Defined in Language.Syntactic.Syntax |
appSym :: (ApplySym sig f dom, sym :<: AST dom) => sym sig -> f Source #
Generic symbol application
appSym
has any type of the form:
appSym :: (expr :<: AST dom) => expr (a :-> b :-> ... :-> Full x) -> (ASTF dom a -> ASTF dom b -> ... -> ASTF dom x)