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

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Constructs.Decoration

Contents

Description

Construct for decorating expressions with additional information

Synopsis

Decoration

data Decor info expr sig where Source #

Decorating symbols with additional information

One usage of Decor is to decorate every node of a syntax tree. This is done simply by changing

AST dom sig

to

AST (Decor info dom) sig

Constructors

Decor :: {..} -> Decor info expr sig 

Fields

Instances
Project sub sup => Project sub (Decor info sup) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Methods

prj :: Decor info sup a -> Maybe (sub a) Source #

StringTree expr => StringTree (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Methods

stringTreeSym :: [Tree String] -> Decor info expr a -> Tree String Source #

Render expr => Render (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Methods

renderSym :: Decor info expr sig -> String Source #

renderArgs :: [String] -> Decor info expr sig -> String Source #

Eval expr => Eval (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Methods

evaluate :: Decor info expr a -> Denotation a Source #

Equality expr => Equality (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Methods

equal :: Decor info expr a -> Decor info expr b -> Bool Source #

exprHash :: Decor info expr a -> Hash Source #

Constrained expr => Constrained (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Associated Types

type Sat (Decor info expr) :: * -> Constraint Source #

Methods

exprDict :: Decor info expr a -> Dict (Sat (Decor info expr) (DenResult a)) Source #

EvalBind dom => EvalBind (Decor info dom) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Binding

Methods

evalBindSym :: (EvalBind dom0, ConstrainedBy dom0 Typeable, Typeable (DenResult sig)) => Decor info dom sig -> Args (AST dom0) sig -> Reader [(VarId, Dynamic)] (DenResult sig) Source #

AlphaEq sub sub dom env => AlphaEq (Decor info sub) (Decor info sub) dom env Source # 
Instance details

Defined in Language.Syntactic.Constructs.Binding

Methods

alphaEqSym :: Decor info sub a -> Args (AST dom) a -> Decor info sub b -> Args (AST dom) b -> Reader env Bool Source #

type Sat (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

type Sat (Decor info expr) = Sat expr

getInfo :: AST (Decor info dom) sig -> info (DenResult sig) Source #

Get the decoration of the top-level node

updateDecor :: forall info dom a. (info a -> info a) -> ASTF (Decor info dom) a -> ASTF (Decor info dom) a Source #

Update the decoration of the top-level node

liftDecor :: (expr s -> info (DenResult s) -> b) -> Decor info expr s -> b Source #

Lift a function that operates on expressions with associated information to operate on an Decor expression. This function is convenient to use together with e.g. queryNodeSimple when the domain has the form (Decor info dom).

collectInfo :: (forall sig. info sig -> b) -> AST (Decor info dom) a -> [b] Source #

Collect the decorations of all nodes

stringTreeDecor :: forall info dom a. StringTree dom => (forall sig. info sig -> String) -> ASTF (Decor info dom) a -> Tree String Source #

Rendering of decorated syntax trees

showDecorWith :: StringTree dom => (forall sig. info sig -> String) -> ASTF (Decor info dom) a -> String Source #

Show an decorated syntax tree using ASCII art

drawDecorWith :: StringTree dom => (forall sig. info sig -> String) -> ASTF (Decor info dom) a -> IO () Source #

Print an decorated syntax tree using ASCII art

writeHtmlDecorWith :: forall info sym a. StringTree sym => (forall sig. info sig -> String) -> FilePath -> ASTF (Decor info sym) a -> IO () Source #

stripDecor :: AST (Decor info dom) sig -> AST dom sig Source #

Strip decorations from an AST