syntactic-1.17: Generic abstract syntax, and utilities for embedded languages

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Interpretation.Equality

Contents

Synopsis

Documentation

class Equality expr where Source #

Equality for expressions

Methods

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

Equality for expressions

Comparing expressions of different types is often needed when dealing with expressions with existentially quantified sub-terms.

exprHash :: expr a -> Hash Source #

Computes a Hash for an expression. Expressions that are equal according to equal must result in the same hash:

equal a b  ==>  exprHash a == exprHash b

equal :: Semantic expr => expr a -> expr b -> Bool Source #

Equality for expressions

Comparing expressions of different types is often needed when dealing with expressions with existentially quantified sub-terms.

exprHash :: Semantic expr => expr a -> Hash Source #

Computes a Hash for an expression. Expressions that are equal according to equal must result in the same hash:

equal a b  ==>  exprHash a == exprHash b
Instances
Equality Semantics Source # 
Instance details

Defined in Language.Syntactic.Interpretation.Equality

Equality Empty Source # 
Instance details

Defined in Language.Syntactic.Constraint

Methods

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

exprHash :: Empty a -> Hash Source #

Equality Tuple Source # 
Instance details

Defined in Language.Syntactic.Constructs.Tuple

Methods

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

exprHash :: Tuple a -> Hash Source #

Equality Select Source # 
Instance details

Defined in Language.Syntactic.Constructs.Tuple

Methods

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

exprHash :: Select a -> Hash Source #

Equality Literal Source # 
Instance details

Defined in Language.Syntactic.Constructs.Literal

Equality Identity Source # 
Instance details

Defined in Language.Syntactic.Constructs.Identity

Equality Construct Source # 
Instance details

Defined in Language.Syntactic.Constructs.Construct

Equality Condition Source # 
Instance details

Defined in Language.Syntactic.Constructs.Condition

Equality Let Source # 
Instance details

Defined in Language.Syntactic.Constructs.Binding

Methods

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

exprHash :: Let a -> Hash Source #

Equality Lambda Source #

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

exprHash assigns the same hash to all Lambda bindings. This is a valid over-approximation that enables the following property:

alphaEq a b  ==>  exprHash a == exprHash b
Instance details

Defined in Language.Syntactic.Constructs.Binding

Methods

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

exprHash :: Lambda a -> Hash Source #

Equality Variable Source #

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

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

alphaEq a b  ==>  exprHash a == exprHash b
Instance details

Defined in Language.Syntactic.Constructs.Binding

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

Defined in Language.Syntactic.Interpretation.Equality

Methods

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

exprHash :: AST dom a -> Hash Source #

Monad m => Equality (MONAD m) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Monad

Methods

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

exprHash :: MONAD m a -> Hash Source #

(Equality expr1, Equality expr2) => Equality (expr1 :+: expr2) Source # 
Instance details

Defined in Language.Syntactic.Interpretation.Equality

Methods

equal :: (expr1 :+: expr2) a -> (expr1 :+: expr2) b -> Bool Source #

exprHash :: (expr1 :+: expr2) a -> Hash Source #

Equality dom => Equality (dom :|| pred) Source # 
Instance details

Defined in Language.Syntactic.Constraint

Methods

equal :: (dom :|| pred) a -> (dom :|| pred) b -> Bool Source #

exprHash :: (dom :|| pred) a -> Hash Source #

Equality dom => Equality (dom :| pred) Source # 
Instance details

Defined in Language.Syntactic.Constraint

Methods

equal :: (dom :| pred) a -> (dom :| pred) b -> Bool Source #

exprHash :: (dom :| pred) a -> Hash Source #

Equality expr => Equality (Decor info expr) Source # 
Instance details

Defined in Language.Syntactic.Constructs.Decoration

Methods

equal :: Decor info expr a -> Decor info expr b -> Bool Source #

exprHash :: Decor info expr a -> Hash Source #

Equality dom => Equality (SubConstr1 c dom p) Source # 
Instance details

Defined in Language.Syntactic.Constraint

Methods

equal :: SubConstr1 c dom p a -> SubConstr1 c dom p b -> Bool Source #

exprHash :: SubConstr1 c dom p a -> Hash Source #

Equality dom => Equality (SubConstr2 c dom pa pb) Source # 
Instance details

Defined in Language.Syntactic.Constraint

Methods

equal :: SubConstr2 c dom pa pb a -> SubConstr2 c dom pa pb b -> Bool Source #

exprHash :: SubConstr2 c dom pa pb a -> Hash Source #

equalDefault :: Semantic expr => expr a -> expr b -> Bool Source #

Default implementation of equal

exprHashDefault :: Semantic expr => expr a -> Hash Source #

Default implementation of exprHash

Orphan instances

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

Methods

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

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

(Equality expr1, Equality expr2) => Eq ((expr1 :+: expr2) a) Source # 
Instance details

Methods

(==) :: (expr1 :+: expr2) a -> (expr1 :+: expr2) a -> Bool #

(/=) :: (expr1 :+: expr2) a -> (expr1 :+: expr2) a -> Bool #