| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
AST.Class.ZipMatch
Description
A class to match term structures
Synopsis
- class ZipMatch k where
- 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)
- 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))
- 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 ())
- 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 ())
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 # | |
| ZipMatch Prune Source # | |
| Eq a => ZipMatch (Ann a) Source # | |
| ZipMatch (FuncType typ) Source # | |
| ZipMatch (App expr) Source # | |
| Eq a => ZipMatch (Const a :: Knot -> Type) Source # | |
| (ZipMatch k0, ZipMatch k1, KTraversable k0, KFunctor k1) => ZipMatch (Compose k0 k1) Source # | |
| Eq k => ZipMatch (TermMap k expr) Source # | |
| (Eq nomId, ZipMatch varTypes, KTraversable varTypes, KNodesConstraint varTypes ZipMatch, KNodesConstraint varTypes OrdQVar) => ZipMatch (NominalInst nomId varTypes) Source # | |
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 # | |
| Eq a => ZipMatch (ScopeVar expr a) Source # | |
| (ZipMatch a, ZipMatch b) => ZipMatch (Product a b) Source # | |
| (ZipMatch a, ZipMatch b) => ZipMatch (Sum a b) Source # | |
| Eq key => ZipMatch (RowExtend key val rest) 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 #
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 #