| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Syntactic.Interpretation
Description
Equality and rendering of ASTs
Synopsis
- class Equality e where
- class Render sym where
- renderSym :: sym sig -> String
- renderArgs :: [String] -> sym sig -> String
- renderArgsSmart :: Render sym => [String] -> sym a -> String
- render :: forall sym a. Render sym => ASTF sym a -> String
- class Render sym => StringTree sym where
- stringTreeSym :: [Tree String] -> sym a -> Tree String
- stringTree :: forall sym a. StringTree sym => ASTF sym a -> Tree String
- showAST :: StringTree sym => ASTF sym a -> String
- drawAST :: StringTree sym => ASTF sym a -> IO ()
- writeHtmlAST :: StringTree sym => FilePath -> ASTF sym a -> IO ()
- equalDefault :: Render sym => sym a -> sym b -> Bool
- hashDefault :: Render sym => sym a -> Hash
Equality
class Equality e where Source #
Higher-kinded equality
Minimal complete definition
Nothing
Methods
equal :: e a -> e b -> Bool Source #
Higher-kinded equality
Comparing elements of different types is often needed when dealing with expressions with existentially quantified sub-terms.
Higher-kinded hashing. Elements that are equal according to equal must result in the same
hash:
equal a b ==> hash a == hash b
Instances
| Equality Empty Source # | |
| Equality Let Source # | |
| Equality BindingT Source # |
|
| Equality Binding Source # |
|
| Equality Construct Source # | |
| Equality Literal Source # | |
| Equality Tuple Source # | |
| Equality sym => Equality (Typed sym) Source # | |
| Equality sym => Equality (AST sym) Source # | |
| Equality (MONAD m) Source # | |
| (Equality sym1, Equality sym2) => Equality (sym1 :+: sym2) Source # | |
| Equality expr => Equality (expr :&: info) Source # | |
Rendering
class Render sym where Source #
Render a symbol as concrete syntax. A complete instance must define at least the renderSym
method.
Minimal complete definition
Methods
renderSym :: sym sig -> String Source #
Show a symbol as a String
renderArgs :: [String] -> sym sig -> String Source #
Render a symbol given a list of rendered arguments
Instances
| Render Empty Source # | |
| Render Let Source # | |
| Render BindingT Source # | |
| Render Binding Source # | |
| Render Construct Source # | |
| Render Literal Source # | |
| Render Tuple Source # | |
| Render sym => Render (Typed sym) Source # | |
| Render (MONAD m) Source # | |
| (Render sym1, Render sym2) => Render (sym1 :+: sym2) Source # | |
| Render expr => Render (expr :&: info) Source # | |
renderArgsSmart :: Render sym => [String] -> sym a -> String Source #
Implementation of renderArgs that handles infix operators
class Render sym => StringTree sym where Source #
Convert a symbol to a Tree of strings
Minimal complete definition
Nothing
Methods
stringTreeSym :: [Tree String] -> sym a -> Tree String Source #
Convert a symbol to a Tree given a list of argument trees
Instances
| StringTree Empty Source # | |
Defined in Language.Syntactic.Interpretation | |
| StringTree Let Source # | |
Defined in Language.Syntactic.Functional | |
| StringTree BindingT Source # | |
Defined in Language.Syntactic.Functional | |
| StringTree Binding Source # | |
Defined in Language.Syntactic.Functional | |
| StringTree Construct Source # | |
Defined in Language.Syntactic.Functional | |
| StringTree Literal Source # | |
Defined in Language.Syntactic.Functional | |
| StringTree Tuple Source # | |
Defined in Language.Syntactic.Functional.Tuple | |
| StringTree sym => StringTree (Typed sym) Source # | |
Defined in Language.Syntactic.Interpretation | |
| StringTree (MONAD m) Source # | |
Defined in Language.Syntactic.Functional | |
| (StringTree sym1, StringTree sym2) => StringTree (sym1 :+: sym2) Source # | |
Defined in Language.Syntactic.Interpretation | |
| StringTree expr => StringTree (expr :&: info) Source # | |
Defined in Language.Syntactic.Decoration | |
stringTree :: forall sym a. StringTree sym => ASTF sym a -> Tree String Source #
writeHtmlAST :: StringTree sym => FilePath -> ASTF sym a -> IO () Source #
Write a syntax tree to an HTML file with foldable nodes