Safe Haskell | None |
---|---|
Language | Haskell2010 |
Construct for decorating symbols or expressions with additional information
- data (expr :&: info) sig where
- mapDecor :: (sym1 sig -> sym2 sig) -> (info1 (DenResult sig) -> info2 (DenResult sig)) -> (sym1 :&: info1) sig -> (sym2 :&: info2) sig
- getDecor :: AST (sym :&: info) sig -> info (DenResult sig)
- updateDecor :: forall info sym a. (info a -> info a) -> ASTF (sym :&: info) a -> ASTF (sym :&: info) a
- liftDecor :: (expr s -> info (DenResult s) -> b) -> (expr :&: info) s -> b
- stripDecor :: AST (sym :&: info) sig -> AST sym sig
- stringTreeDecor :: forall info sym a. StringTree sym => (forall a. info a -> String) -> ASTF (sym :&: info) a -> Tree String
- showDecorWith :: StringTree sym => (forall a. info a -> String) -> ASTF (sym :&: info) a -> String
- drawDecorWith :: StringTree sym => (forall a. info a -> String) -> ASTF (sym :&: info) a -> IO ()
- writeHtmlDecorWith :: forall info sym a. StringTree sym => (forall b. info b -> String) -> FilePath -> ASTF (sym :&: info) a -> IO ()
- smartSymDecor :: (Signature sig, f ~ SmartFun (sup :&: info) sig, sig ~ SmartSig f, (sup :&: info) ~ SmartSym f, sub :<: sup) => info (DenResult sig) -> sub sig -> f
- 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
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
Project sub sup => Project sub ((:&:) sup info) Source # | |
(NFData1 sym, NFData1 info) => NFData1 ((:&:) sym info) Source # | |
Symbol sym => Symbol ((:&:) sym info) Source # | |
StringTree expr => StringTree ((:&:) expr info) Source # | |
Render expr => Render ((:&:) expr info) Source # | |
Equality expr => Equality ((:&:) expr info) Source # | |
Eval sym => Eval ((:&:) sym info) Source # | |
BindingDomain sym => BindingDomain ((:&:) sym i) Source # | |
EvalEnv sym env => EvalEnv ((:&:) sym info) env 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
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)