syntactic-3.2: Generic representation and manipulation of abstract syntax

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Syntax

Contents

Description

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

Syntax trees

data AST sym sig where Source

Generic abstract syntax tree, parameterized by a symbol domain

(AST sym (a :-> b)) represents a partially applied (or unapplied) symbol, missing at least one argument, while (AST sym (Full a)) represents a fully applied symbol, i.e. a complete syntax tree.

Constructors

Sym :: sym sig -> AST sym sig 
(:$) :: AST sym (a :-> sig) -> AST sym (Full a) -> AST sym sig infixl 1 

Instances

(:<:) sub sup => sub :<: (AST sup) Source 
Project sub sup => Project sub (AST sup) Source 
Functor sym => Functor (AST sym) Source 
Equality sym => Equality (AST sym) Source 
BindingDomain sym => BindingDomain (AST sym) Source 
NFData1 sym => NFData (AST sym sig) Source 
Syntactic (ASTF sym a) Source 
(Syntactic a, (~) (* -> *) (Domain a) sym, (~) * ia (Internal a), SyntacticN f fi) => SyntacticN (a -> f) (AST sym (Full ia) -> fi) Source 
type SmartSym (AST sym sig) = sym Source 
type SmartSig (ASTF sym a -> f) = (:->) a (SmartSig f) Source 
type SmartSig (AST sym sig) = sig Source 
type Domain (ASTF sym a) = sym Source 
type Internal (ASTF sym a) = a Source 

type ASTF sym a = AST sym (Full a) Source

Fully applied abstract syntax tree

newtype Full a Source

Signature of a fully applied symbol

Constructors

Full 

Fields

result :: a
 

Instances

Functor Full Source 
Eq a => Eq (Full a) Source 
Show a => Show (Full a) Source 
Signature (Full a) Source 
Syntactic (ASTF sym a) Source 
(Syntactic a, (~) (* -> *) (Domain a) sym, (~) * ia (Internal a), SyntacticN f fi) => SyntacticN (a -> f) (AST sym (Full ia) -> fi) Source 
type SmartFun sym (Full a) = ASTF sym a Source 
type DenotationM m (Full a) = m a Source 
type LiftReader env (Full a) = Full (Reader env a) Source 
type DenResult (Full a) = a Source 
type Denotation (Full a) = a Source 
type LowerReader (Full a) = Full (UnReader a) Source 
type SmartSig (ASTF sym a -> f) = (:->) a (SmartSig f) Source 
type Domain (ASTF sym a) = sym Source 
type Internal (ASTF sym a) = a Source 

newtype a :-> sig infixr 9 Source

Signature of a partially applied (or unapplied) symbol

Constructors

Partial (a -> sig) 

Instances

Functor ((:->) a) Source 
Signature sig => Signature ((:->) a sig) Source 
type SmartFun sym ((:->) a sig) = ASTF sym a -> SmartFun sym sig Source 
type DenotationM m ((:->) a sig) = m a -> DenotationM m sig Source 
type LiftReader env ((:->) a sig) = (:->) (Reader env a) (LiftReader env sig) Source 
type DenResult ((:->) a sig) = DenResult sig Source 
type Denotation ((:->) a sig) = a -> Denotation sig Source 
type LowerReader ((:->) a sig) = (:->) (UnReader a) (LowerReader sig) Source 

data SigRep sig where Source

Witness of the arity of a symbol signature

Constructors

SigFull :: SigRep (Full a) 
SigMore :: SigRep sig -> SigRep (a :-> sig) 

class Signature sig where Source

Valid symbol signatures

Methods

signature :: SigRep sig Source

Instances

type family DenResult sig Source

The result type of a symbol with the given signature

Instances

type DenResult (Full a) = a Source 
type DenResult ((:->) a sig) = DenResult sig Source 

class Symbol sym where Source

Valid symbols to use in an AST

Methods

symSig :: sym sig -> SigRep sig Source

Reify the signature of a symbol

size :: AST sym sig -> Int Source

Count the number of symbols in an AST

Smart constructors

type family SmartFun sym sig Source

Maps a symbol signature to the type of the corresponding smart constructor:

SmartFun sym (a :-> b :-> ... :-> Full x) = ASTF sym a -> ASTF sym b -> ... -> ASTF sym x

Instances

type SmartFun sym (Full a) = ASTF sym a Source 
type SmartFun sym ((:->) a sig) = ASTF sym a -> SmartFun sym sig Source 

type family SmartSig f Source

Maps a smart constructor type to the corresponding symbol signature:

SmartSig (ASTF sym a -> ASTF sym b -> ... -> ASTF sym x) = a :-> b :-> ... :-> Full x

Instances

type SmartSig (ASTF sym a -> f) = (:->) a (SmartSig f) Source 
type SmartSig (AST sym sig) = sig Source 

type family SmartSym f :: * -> * Source

Returns the symbol in the result of a smart constructor

Instances

type SmartSym (a -> f) = SmartSym f Source 
type SmartSym (AST sym sig) = sym Source 

smartSym' :: forall sig f sym. (Signature sig, f ~ SmartFun sym sig, sig ~ SmartSig f, sym ~ SmartSym f) => sym sig -> f Source

Make a smart constructor of a symbol. smartSym has any type of the form:

smartSym
    :: sym (a :-> b :-> ... :-> Full x)
    -> (ASTF sym a -> ASTF sym b -> ... -> ASTF sym x)

Open symbol domains

data (sym1 :+: sym2) sig where infixr 9 Source

Direct sum of two symbol domains

Constructors

InjL :: sym1 a -> (sym1 :+: sym2) a 
InjR :: sym2 a -> (sym1 :+: sym2) a 

Instances

(:<:) sym1 sym3 => sym1 :<: ((:+:) sym2 sym3) Source 
sym1 :<: ((:+:) sym1 sym2) Source 
Project sym1 sym3 => Project sym1 ((:+:) sym2 sym3) Source 
Project sym1 ((:+:) sym1 sym2) Source 
(Functor sym1, Functor sym2) => Functor ((:+:) sym1 sym2) Source 
(Foldable sym1, Foldable sym2) => Foldable ((:+:) sym1 sym2) Source 
(Traversable sym1, Traversable sym2) => Traversable ((:+:) sym1 sym2) Source 
(NFData1 sym1, NFData1 sym2) => NFData1 ((:+:) sym1 sym2) Source 
(Symbol sym1, Symbol sym2) => Symbol ((:+:) sym1 sym2) Source 
(StringTree sym1, StringTree sym2) => StringTree ((:+:) sym1 sym2) Source 
(Render sym1, Render sym2) => Render ((:+:) sym1 sym2) Source 
(Equality sym1, Equality sym2) => Equality ((:+:) sym1 sym2) Source 
(Eval s, Eval t) => Eval ((:+:) s t) Source 
(BindingDomain sym1, BindingDomain sym2) => BindingDomain ((:+:) sym1 sym2) Source 
(EvalEnv sym1 env, EvalEnv sym2 env) => EvalEnv ((:+:) sym1 sym2) env Source 

class Project sub sup where Source

Symbol projection

The class is defined for all pairs of types, but prj can only succeed if sup is of the form (... :+: sub :+: ...).

Methods

prj :: sup a -> Maybe (sub a) Source

Partial projection from sup to sub

Instances

Project sub sup Source

If sub is not in sup, prj always returns Nothing.

Project sym sym Source 
Project sub sup => Project sub (Typed sup) Source 
Project sub sup => Project sub (AST sup) Source 
Project sym1 sym3 => Project sym1 ((:+:) sym2 sym3) Source 
Project sym1 ((:+:) sym1 sym2) Source 
Project sub sup => Project sub ((:&:) sup info) Source 

class Project sub sup => sub :<: sup where Source

Symbol injection

The class includes types sub and sup where sup is of the form (... :+: sub :+: ...).

Methods

inj :: sub a -> sup a Source

Injection from sub to sup

Instances

sym :<: sym Source 
(:<:) sub sup => sub :<: (AST sup) Source 
(:<:) sym1 sym3 => sym1 :<: ((:+:) sym2 sym3) Source 
sym1 :<: ((:+:) sym1 sym2) Source 

smartSym :: (Signature sig, f ~ SmartFun sup sig, sig ~ SmartSig f, sup ~ SmartSym f, sub :<: sup) => sub sig -> f Source

Make a smart constructor of a symbol. smartSym has any type of the form:

smartSym :: (sub :<: AST sup)
    => sub (a :-> b :-> ... :-> Full x)
    -> (ASTF sup a -> ASTF sup b -> ... -> ASTF sup x)

smartSymTyped :: (Signature sig, f ~ SmartFun (Typed sup) sig, sig ~ SmartSig f, Typed sup ~ SmartSym f, sub :<: sup, Typeable (DenResult sig)) => sub sig -> f Source

Make a smart constructor of a symbol. smartSymTyped has any type of the form:

smartSymTyped :: (sub :<: AST (Typed sup), Typeable x)
    => sub (a :-> b :-> ... :-> Full x)
    -> (ASTF sup a -> ASTF sup b -> ... -> ASTF sup x)

data Empty :: * -> * Source

Empty symbol type

Can be used to make uninhabited AST types. It can also be used as a terminator in co-product lists (e.g. to avoid overlapping instances):

(A :+: B :+: Empty)

Existential quantification

data E e where Source

Existential quantification

Constructors

E :: e a -> E e 

liftE :: (forall a. e a -> b) -> E e -> b Source

liftE2 :: (forall a b. e a -> e b -> c) -> E e -> E e -> c Source

data EF e where Source

Existential quantification of Full-indexed type

Constructors

EF :: e (Full a) -> EF e 

liftEF :: (forall a. e (Full a) -> b) -> EF e -> b Source

liftEF2 :: (forall a b. e (Full a) -> e (Full b) -> c) -> EF e -> EF e -> c Source

Type casting expressions

data Typed sym sig where Source

"Typed" symbol. Using Typed sym instead of sym gives access to the function castExpr for casting expressions.

Constructors

Typed :: Typeable (DenResult sig) => sym sig -> Typed sym sig 

Instances

Project sub sup => Project sub (Typed sup) Source 
StringTree sym => StringTree (Typed sym) Source 
Render sym => Render (Typed sym) Source 
Equality sym => Equality (Typed sym) Source 
BindingDomain sym => BindingDomain (Typed sym) Source 
EvalEnv sym env => EvalEnv (Typed sym) env Source 

injT :: (sub :<: sup, Typeable (DenResult sig)) => sub sig -> AST (Typed sup) sig Source

Inject a symbol in an AST with a Typed domain

castExpr Source

Arguments

:: ASTF (Typed sym) a

Expression to cast

-> ASTF (Typed sym) b

Witness for typeability of result

-> Maybe (ASTF (Typed sym) b) 

Type cast an expression

Misc.

class NFData1 c where Source

Higher-kinded version of NFData

Minimal complete definition

Nothing

Methods

rnf1 :: c a -> () Source

Force a symbol to normal form

Instances

symType :: Proxy sym -> sym sig -> sym sig Source

Constrain a symbol to a specific type

prjP :: Project sub sup => Proxy sub -> sup sig -> Maybe (sub sig) Source

Projection to a specific symbol type