| Safe Haskell | None |
|---|
Language.Syntactic.Constructs.Decoration
Contents
Description
Construct for decorating expressions with additional information
- data Decor info expr a where
- injDecor :: (sub :<: sup, Signature a) => info (DenResult a) -> sub a -> AST (Decor info sup) a
- prjDecor :: sub :<: sup => AST (Decor info sup) a -> Maybe (info (DenResult a), sub a)
- injDecorCtx :: (sub ctx :<: sup, Signature a) => Proxy ctx -> info (DenResult a) -> sub ctx a -> AST (Decor info sup) a
- prjDecorCtx :: sub ctx :<: sup => Proxy ctx -> AST (Decor info sup) a -> Maybe (info (DenResult a), sub ctx a)
- getInfo :: AST (Decor info dom) a -> info (DenResult a)
- updateDecor :: forall info dom a. (info a -> info a) -> ASTF (Decor info dom) a -> ASTF (Decor info dom) a
- liftDecor :: (expr a -> info (DenResult a) -> b) -> Decor info expr a -> b
- collectInfo :: (forall a. info a -> b) -> AST (Decor info dom) a -> [b]
- toTreeDecor :: forall info dom a. (Render info, ToTree dom) => ASTF (Decor info dom) a -> Tree String
- showDecor :: (Render info, ToTree dom) => ASTF (Decor info dom) a -> String
- drawDecor :: (Render info, ToTree dom) => ASTF (Decor info dom) a -> IO ()
- stripDecor :: AST (Decor info dom) a -> AST dom a
Decoration
data Decor info expr a whereSource
Decorating an expression with additional information
One usage of Decor is to decorate every node of a syntax tree. This is done
simply by changing
AST dom a
to
AST (Decor info dom) a
Injection/projection of an decorated tree is done using injDecor /
prjDecor.
Instances
| MaybeWitnessSat ctx dom => MaybeWitnessSat ctx (Decor info dom) | |
| WitnessSat expr => WitnessSat (Decor info expr) | |
| WitnessCons dom => WitnessCons (Decor info dom) | |
| ExprEq expr => ExprEq (Decor info expr) | |
| ToTree expr => ToTree (Decor info expr) | |
| Render expr => Render (Decor info expr) | |
| Eval expr => Eval (Decor info expr) | |
| EvalBind dom => EvalBind (Decor info dom) | |
| AlphaEq dom dom (Decor info dom) env => AlphaEq (Decor info dom) (Decor info dom) (Decor info dom) env |
injDecor :: (sub :<: sup, Signature a) => info (DenResult a) -> sub a -> AST (Decor info sup) aSource
injDecorCtx :: (sub ctx :<: sup, Signature a) => Proxy ctx -> info (DenResult a) -> sub ctx a -> AST (Decor info sup) aSource
injDecor with explicit context
prjDecorCtx :: sub ctx :<: sup => Proxy ctx -> AST (Decor info sup) a -> Maybe (info (DenResult a), sub ctx a)Source
prjDecor with explicit context
getInfo :: AST (Decor info dom) a -> info (DenResult a)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) aSource
Update the decoration of the top-level node
liftDecor :: (expr a -> info (DenResult a) -> b) -> Decor info expr a -> bSource
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 a. info a -> b) -> AST (Decor info dom) a -> [b]Source
Collect the decorations of all nodes
toTreeDecor :: forall info dom a. (Render info, ToTree dom) => ASTF (Decor info dom) a -> Tree StringSource
Rendering of decorated syntax trees
showDecor :: (Render info, ToTree dom) => ASTF (Decor info dom) a -> StringSource
Show an decorated syntax tree using ASCII art