syntactic-3.8: Generic representation and manipulation of abstract syntax

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Interpretation

Contents

Description

Equality and rendering of ASTs

Synopsis

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.

equal :: Render e => 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.

hash :: e a -> Hash Source #

Higher-kinded hashing. Elements that are equal according to equal must result in the same hash:

equal a b  ==>  hash a == hash b

hash :: Render e => e a -> Hash Source #

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 # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

equal :: Empty a -> Empty b -> Bool Source #

hash :: Empty a -> Hash Source #

Equality Let Source # 
Instance details

Defined in Language.Syntactic.Functional

Methods

equal :: Let a -> Let b -> Bool Source #

hash :: Let a -> Hash Source #

Equality BindingT Source #

equal does strict identifier comparison; i.e. no alpha equivalence.

hash assigns the same hash to all variables and binders. This is a valid over-approximation that enables the following property:

alphaEq a b ==> hash a == hash b
Instance details

Defined in Language.Syntactic.Functional

Methods

equal :: BindingT a -> BindingT b -> Bool Source #

hash :: BindingT a -> Hash Source #

Equality Binding Source #

equal does strict identifier comparison; i.e. no alpha equivalence.

hash assigns the same hash to all variables and binders. This is a valid over-approximation that enables the following property:

alphaEq a b ==> hash a == hash b
Instance details

Defined in Language.Syntactic.Functional

Methods

equal :: Binding a -> Binding b -> Bool Source #

hash :: Binding a -> Hash Source #

Equality Construct Source # 
Instance details

Defined in Language.Syntactic.Functional

Equality Literal Source # 
Instance details

Defined in Language.Syntactic.Functional

Methods

equal :: Literal a -> Literal b -> Bool Source #

hash :: Literal a -> Hash Source #

Equality Tuple Source # 
Instance details

Defined in Language.Syntactic.Functional.Tuple

Methods

equal :: Tuple a -> Tuple b -> Bool Source #

hash :: Tuple a -> Hash Source #

Equality sym => Equality (Typed sym) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

equal :: Typed sym a -> Typed sym b -> Bool Source #

hash :: Typed sym a -> Hash Source #

Equality sym => Equality (AST sym) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

equal :: AST sym a -> AST sym b -> Bool Source #

hash :: AST sym a -> Hash Source #

Equality (MONAD m) Source # 
Instance details

Defined in Language.Syntactic.Functional

Methods

equal :: MONAD m a -> MONAD m b -> Bool Source #

hash :: MONAD m a -> Hash Source #

(Equality sym1, Equality sym2) => Equality (sym1 :+: sym2) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

equal :: (sym1 :+: sym2) a -> (sym1 :+: sym2) b -> Bool Source #

hash :: (sym1 :+: sym2) a -> Hash Source #

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

Defined in Language.Syntactic.Decoration

Methods

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

hash :: (expr :&: info) a -> Hash 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

renderSym

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 # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

renderSym :: Empty sig -> String Source #

renderArgs :: [String] -> Empty sig -> String Source #

Render Let Source # 
Instance details

Defined in Language.Syntactic.Functional

Methods

renderSym :: Let sig -> String Source #

renderArgs :: [String] -> Let sig -> String Source #

Render BindingT Source # 
Instance details

Defined in Language.Syntactic.Functional

Render Binding Source # 
Instance details

Defined in Language.Syntactic.Functional

Render Construct Source # 
Instance details

Defined in Language.Syntactic.Functional

Render Literal Source # 
Instance details

Defined in Language.Syntactic.Functional

Render Tuple Source # 
Instance details

Defined in Language.Syntactic.Functional.Tuple

Methods

renderSym :: Tuple sig -> String Source #

renderArgs :: [String] -> Tuple sig -> String Source #

Render sym => Render (Typed sym) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

renderSym :: Typed sym sig -> String Source #

renderArgs :: [String] -> Typed sym sig -> String Source #

Render (MONAD m) Source # 
Instance details

Defined in Language.Syntactic.Functional

Methods

renderSym :: MONAD m sig -> String Source #

renderArgs :: [String] -> MONAD m sig -> String Source #

(Render sym1, Render sym2) => Render (sym1 :+: sym2) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

renderSym :: (sym1 :+: sym2) sig -> String Source #

renderArgs :: [String] -> (sym1 :+: sym2) sig -> String Source #

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

Defined in Language.Syntactic.Decoration

Methods

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

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

renderArgsSmart :: Render sym => [String] -> sym a -> String Source #

Implementation of renderArgs that handles infix operators

render :: forall sym a. Render sym => ASTF sym a -> String Source #

Render an AST as concrete syntax

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 # 
Instance details

Defined in Language.Syntactic.Interpretation

StringTree Let Source # 
Instance details

Defined in Language.Syntactic.Functional

StringTree BindingT Source # 
Instance details

Defined in Language.Syntactic.Functional

StringTree Binding Source # 
Instance details

Defined in Language.Syntactic.Functional

StringTree Construct Source # 
Instance details

Defined in Language.Syntactic.Functional

StringTree Literal Source # 
Instance details

Defined in Language.Syntactic.Functional

StringTree Tuple Source # 
Instance details

Defined in Language.Syntactic.Functional.Tuple

StringTree sym => StringTree (Typed sym) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

stringTreeSym :: [Tree String] -> Typed sym a -> Tree String Source #

StringTree (MONAD m) Source # 
Instance details

Defined in Language.Syntactic.Functional

(StringTree sym1, StringTree sym2) => StringTree (sym1 :+: sym2) Source # 
Instance details

Defined in Language.Syntactic.Interpretation

Methods

stringTreeSym :: [Tree String] -> (sym1 :+: sym2) a -> Tree String Source #

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

Defined in Language.Syntactic.Decoration

Methods

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

stringTree :: forall sym a. StringTree sym => ASTF sym a -> Tree String Source #

Convert an AST to a Tree of strings

showAST :: StringTree sym => ASTF sym a -> String Source #

Show a syntax tree using ASCII art

drawAST :: StringTree sym => ASTF sym a -> IO () Source #

Print a syntax tree using ASCII art

writeHtmlAST :: StringTree sym => FilePath -> ASTF sym a -> IO () Source #

Write a syntax tree to an HTML file with foldable nodes

Default interpretation

equalDefault :: Render sym => sym a -> sym b -> Bool Source #

Default implementation of equal

hashDefault :: Render sym => sym a -> Hash Source #

Default implementation of hash

Orphan instances

Equality sym => Eq (AST sym a) Source # 
Instance details

Methods

(==) :: AST sym a -> AST sym a -> Bool #

(/=) :: AST sym a -> AST sym a -> Bool #

Render sym => Show (ASTF sym a) Source # 
Instance details

Methods

showsPrec :: Int -> ASTF sym a -> ShowS #

show :: ASTF sym a -> String #

showList :: [ASTF sym a] -> ShowS #

(Equality sym1, Equality sym2) => Eq ((sym1 :+: sym2) a) Source # 
Instance details

Methods

(==) :: (sym1 :+: sym2) a -> (sym1 :+: sym2) a -> Bool #

(/=) :: (sym1 :+: sym2) a -> (sym1 :+: sym2) a -> Bool #