syntax-tree-0.1.0.1: Typed ASTs

Safe HaskellNone
LanguageHaskell2010

AST.Class.ZipMatch

Description

A class to match term structures

Synopsis

Documentation

class ZipMatch k where Source #

A class to match term structures.

Similar to a partial version of Apply but the semantics are different - when the terms contain plain values, zipK would append them, but zipMatch would compare them and only produce a result if they match.

The TemplateHaskell generators makeKApply and makeZipMatch create the instances according to these semantics.

Methods

zipMatch :: Tree k p -> Tree k q -> Maybe (Tree k (Product p q)) Source #

Compare two structures

>>> zipMatch (NewPerson p0) (NewPerson p1)
Just (NewPerson (Pair p0 p1))
>>> zipMatch (NewPerson p) (NewCake c)
Nothing
Instances
ZipMatch Pure Source # 
Instance details

Defined in AST.Class.ZipMatch

Methods

zipMatch :: Tree Pure p -> Tree Pure q -> Maybe (Tree Pure (Product p q)) Source #

ZipMatch Prune Source # 
Instance details

Defined in AST.Knot.Prune

Methods

zipMatch :: Tree Prune p -> Tree Prune q -> Maybe (Tree Prune (Product p q)) Source #

Eq a => ZipMatch (Ann a) Source # 
Instance details

Defined in AST.Knot.Ann

Methods

zipMatch :: Tree (Ann a) p -> Tree (Ann a) q -> Maybe (Tree (Ann a) (Product p q)) Source #

ZipMatch (FuncType typ) Source # 
Instance details

Defined in AST.Term.FuncType

Methods

zipMatch :: Tree (FuncType typ) p -> Tree (FuncType typ) q -> Maybe (Tree (FuncType typ) (Product p q)) Source #

ZipMatch (App expr) Source # 
Instance details

Defined in AST.Term.App

Methods

zipMatch :: Tree (App expr) p -> Tree (App expr) q -> Maybe (Tree (App expr) (Product p q)) Source #

Eq a => ZipMatch (Const a :: Knot -> Type) Source # 
Instance details

Defined in AST.Class.ZipMatch

Methods

zipMatch :: Tree (Const a) p -> Tree (Const a) q -> Maybe (Tree (Const a) (Product p q)) Source #

(ZipMatch k0, ZipMatch k1, KTraversable k0, KFunctor k1) => ZipMatch (Compose k0 k1) Source # 
Instance details

Defined in AST.Combinator.Compose

Methods

zipMatch :: Tree (Compose k0 k1) p -> Tree (Compose k0 k1) q -> Maybe (Tree (Compose k0 k1) (Product p q)) Source #

Eq k => ZipMatch (TermMap k expr) Source # 
Instance details

Defined in AST.Term.Map

Methods

zipMatch :: Tree (TermMap k expr) p -> Tree (TermMap k expr) q -> Maybe (Tree (TermMap k expr) (Product p q)) Source #

(Eq nomId, ZipMatch varTypes, KTraversable varTypes, KNodesConstraint varTypes ZipMatch, KNodesConstraint varTypes OrdQVar) => ZipMatch (NominalInst nomId varTypes) Source # 
Instance details

Defined in AST.Term.Nominal

Methods

zipMatch :: Tree (NominalInst nomId varTypes) p -> Tree (NominalInst nomId varTypes) q -> Maybe (Tree (NominalInst nomId varTypes) (Product p q)) Source #

ZipMatch (Scope expr a) Source # 
Instance details

Defined in AST.Term.NamelessScope

Methods

zipMatch :: Tree (Scope expr a) p -> Tree (Scope expr a) q -> Maybe (Tree (Scope expr a) (Product p q)) Source #

Eq a => ZipMatch (ScopeVar expr a) Source # 
Instance details

Defined in AST.Term.NamelessScope

Methods

zipMatch :: Tree (ScopeVar expr a) p -> Tree (ScopeVar expr a) q -> Maybe (Tree (ScopeVar expr a) (Product p q)) Source #

(ZipMatch a, ZipMatch b) => ZipMatch (Product a b) Source # 
Instance details

Defined in AST.Class.ZipMatch

Methods

zipMatch :: Tree (Product a b) p -> Tree (Product a b) q -> Maybe (Tree (Product a b) (Product p q)) Source #

(ZipMatch a, ZipMatch b) => ZipMatch (Sum a b) Source # 
Instance details

Defined in AST.Class.ZipMatch

Methods

zipMatch :: Tree (Sum a b) p -> Tree (Sum a b) q -> Maybe (Tree (Sum a b) (Product p q)) Source #

Eq key => ZipMatch (RowExtend key val rest) Source # 
Instance details

Defined in AST.Term.Row

Methods

zipMatch :: Tree (RowExtend key val rest) p -> Tree (RowExtend key val rest) q -> Maybe (Tree (RowExtend key val rest) (Product p q)) Source #

zipMatch2 :: (ZipMatch k, KFunctor k) => (forall n. KWitness k n -> Tree p n -> Tree q n -> Tree r n) -> Tree k p -> Tree k q -> Maybe (Tree k r) Source #

ZipMatch variant of liftA2

zipMatchA :: (Applicative f, ZipMatch k, KTraversable k) => (forall n. KWitness k n -> Tree p n -> Tree q n -> f (Tree r n)) -> Tree k p -> Tree k q -> Maybe (f (Tree k r)) Source #

An Applicative variant of zipMatch2

zipMatch_ :: (Applicative f, ZipMatch k, KFoldable k) => (forall n. KWitness k n -> Tree p n -> Tree q n -> f ()) -> Tree k p -> Tree k q -> Maybe (f ()) Source #

A variant of zipMatchA where the Applicative actions do not contain results

zipMatch1_ :: (Applicative f, ZipMatch k, KFoldable k, KNodesConstraint k ((~) n)) => (Tree p n -> Tree q n -> f ()) -> Tree k p -> Tree k q -> Maybe (f ()) Source #

A variant of zipMatch_ for Knots with a single node type (avoids using RankNTypes)