syntactic-3.6.2: Generic representation and manipulation of abstract syntax

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Decoration

Description

Construct for decorating symbols or expressions with additional information

Synopsis

Documentation

data (expr :&: info) sig where Source #

Decorating symbols or expressions with additional information

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

AST sym sig

to

AST (sym :&: info) sig

Constructors

(:&:) :: {..} -> (expr :&: info) sig 

Fields

Instances

Project sub sup => Project sub ((:&:) sup info) Source # 

Methods

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

(NFData1 sym, NFData1 info) => NFData1 ((:&:) sym info) Source # 

Methods

rnf1 :: (sym :&: info) a -> () Source #

Symbol sym => Symbol ((:&:) sym info) Source # 

Methods

symSig :: (sym :&: info) sig -> SigRep sig Source #

StringTree expr => StringTree ((:&:) expr info) Source # 

Methods

stringTreeSym :: [Tree String] -> (expr :&: info) a -> Tree String Source #

Render expr => Render ((:&:) expr info) Source # 

Methods

renderSym :: (expr :&: info) sig -> String Source #

renderArgs :: [String] -> (expr :&: info) sig -> String Source #

Equality expr => Equality ((:&:) expr info) Source # 

Methods

equal :: (expr :&: info) a -> (expr :&: info) b -> Bool Source #

hash :: (expr :&: info) a -> Hash Source #

Eval sym => Eval ((:&:) sym info) Source # 

Methods

evalSym :: (sym :&: info) sig -> Denotation sig Source #

BindingDomain sym => BindingDomain ((:&:) sym i) Source # 

Methods

prVar :: (sym :&: i) sig -> Maybe Name Source #

prLam :: (sym :&: i) sig -> Maybe Name Source #

renameBind :: (Name -> Name) -> (sym :&: i) sig -> (sym :&: i) sig Source #

EvalEnv sym env => EvalEnv ((:&:) sym info) env Source # 

Methods

compileSym :: proxy env -> (sym :&: info) sig -> DenotationM (Reader env) sig Source #

mapDecor :: (sym1 sig -> sym2 sig) -> (info1 (DenResult sig) -> info2 (DenResult sig)) -> (sym1 :&: info1) sig -> (sym2 :&: info2) sig Source #

Map over a decoration

getDecor :: AST (sym :&: info) sig -> info (DenResult sig) Source #

Get the decoration of the top-level node

updateDecor :: forall info sym a. (info a -> info a) -> ASTF (sym :&: info) a -> ASTF (sym :&: info) a Source #

Update the decoration of the top-level node

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

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

stripDecor :: AST (sym :&: info) sig -> AST sym sig Source #

Strip decorations from an AST

stringTreeDecor :: forall info sym a. StringTree sym => (forall a. info a -> String) -> ASTF (sym :&: info) a -> Tree String Source #

Rendering of decorated syntax trees

showDecorWith :: StringTree sym => (forall a. info a -> String) -> ASTF (sym :&: info) a -> String Source #

Show an decorated syntax tree using ASCII art

drawDecorWith :: StringTree sym => (forall a. info a -> String) -> ASTF (sym :&: info) a -> IO () Source #

Print an decorated syntax tree using ASCII art

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

smartSymDecor :: (Signature sig, f ~ SmartFun (sup :&: info) sig, sig ~ SmartSig f, (sup :&: info) ~ SmartSym f, sub :<: sup) => info (DenResult sig) -> sub sig -> f Source #

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

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

sugarSymDecor :: (Signature sig, fi ~ SmartFun (sup :&: info) sig, sig ~ SmartSig fi, (sup :&: info) ~ SmartSym fi, SyntacticN f fi, sub :<: sup) => info (DenResult sig) -> sub sig -> f Source #

"Sugared" symbol application

sugarSymDecor has any type of the form:

sugarSymDecor ::
    ( sub :<: AST (sup :&: info)
    , Syntactic a
    , Syntactic b
    , ...
    , Syntactic x
    , Domain a ~ Domain b ~ ... ~ Domain x
    ) => info (Internal x)
      -> sub (Internal a :-> Internal b :-> ... :-> Full (Internal x))
      -> (a -> b -> ... -> x)