mini-egison-0.1.6: Template Haskell Implementation of Egison Pattern Matching

Safe HaskellNone
LanguageHaskell2010

Control.Egison.Matcher

Contents

Description

Matcher definitions.

Synopsis

Something matcher

data Something Source #

Something built-in matcher. The Something matcher can handle only a pattern variable and a wildcard.

Constructors

Something 
Instances
Matcher Something a Source # 
Instance details

Defined in Control.Egison.Matcher

Eql and Integer matchers

class ValuePat m a where Source #

Value patterns.

Methods

valuePat :: (Matcher m a, Eq a) => (HList ctx -> a) -> Pattern a m ctx '[] Source #

Instances
Integral a => ValuePat Integer a Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher Integer a, Eq a) => (HList ctx -> a) -> Pattern a Integer ctx [] Source #

Eq a => ValuePat Eql a Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher Eql a, Eq a) => (HList ctx -> a) -> Pattern a Eql ctx [] Source #

(Matcher m a, Eq a, Ord a, ValuePat m a) => ValuePat (Set m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher (Set m) [a], Eq [a]) => (HList ctx -> [a]) -> Pattern [a] (Set m) ctx [] Source #

(Matcher m a, Eq a, ValuePat m a) => ValuePat (Multiset m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher (Multiset m) [a], Eq [a]) => (HList ctx -> [a]) -> Pattern [a] (Multiset m) ctx [] Source #

(Matcher m a, Eq a, ValuePat m a) => ValuePat (List m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher (List m) [a], Eq [a]) => (HList ctx -> [a]) -> Pattern [a] (List m) ctx [] Source #

data Eql Source #

A matcher for data types that are instances of Eq. The Eql matcher can handle a pattern variable, a wildcard, and a value pattern.

Constructors

Eql 
Instances
Eq a => Matcher Eql a Source # 
Instance details

Defined in Control.Egison.Matcher

Eq a => ValuePat Eql a Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher Eql a, Eq a) => (HList ctx -> a) -> Pattern a Eql ctx [] Source #

data Integer Source #

A matcher for integers. The Integer matcher can handle a pattern variable, a wildcard, and a value pattern.

Constructors

Integer 
Instances
Integral a => Matcher Integer a Source # 
Instance details

Defined in Control.Egison.Matcher

Integral a => ValuePat Integer a Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher Integer a, Eq a) => (HList ctx -> a) -> Pattern a Integer ctx [] Source #

Pair matcher

class PairPat m a where Source #

A pattern constructor for pairs.

Methods

pair :: (Matcher m a, a ~ (b1, b2), m ~ Pair m1 m2) => Pattern b1 m1 ctx xs -> Pattern b2 m2 (ctx :++: xs) ys -> Pattern a m ctx (xs :++: ys) Source #

Instances
(Matcher m1 a1, Matcher m2 a2) => PairPat (Pair m1 m2) (a1, a2) Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

pair :: (Matcher (Pair m1 m2) (a1, a2), (a1, a2) ~ (b1, b2), Pair m1 m2 ~ Pair m10 m20) => Pattern b1 m10 ctx xs -> Pattern b2 m20 (ctx :++: xs) ys -> Pattern (a1, a2) (Pair m1 m2) ctx (xs :++: ys) Source #

data Pair m1 m2 Source #

A matcher for a pair of data.

Constructors

Pair m1 m2 
Instances
(Matcher m1 a1, Matcher m2 a2) => Matcher (Pair m1 m2) (a1, a2) Source # 
Instance details

Defined in Control.Egison.Matcher

(Matcher m1 a1, Matcher m2 a2) => PairPat (Pair m1 m2) (a1, a2) Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

pair :: (Matcher (Pair m1 m2) (a1, a2), (a1, a2) ~ (b1, b2), Pair m1 m2 ~ Pair m10 m20) => Pattern b1 m10 ctx xs -> Pattern b2 m20 (ctx :++: xs) ys -> Pattern (a1, a2) (Pair m1 m2) ctx (xs :++: ys) Source #

Matchers for collections

class CollectionPat m a where Source #

Patterns for collections.

Methods

nil :: Matcher m a => Pattern a m ctx '[] Source #

The nil pattern matches an empty collection.

cons :: (Matcher m a, a ~ [a'], m ~ f m') => Pattern a' m' ctx xs -> Pattern a m (ctx :++: xs) ys -> Pattern a m ctx (xs :++: ys) Source #

The cons pattern decomposes a collection into an element and the rest elements.

join :: Matcher m a => Pattern a m ctx xs -> Pattern a m (ctx :++: xs) ys -> Pattern a m ctx (xs :++: ys) Source #

The join pattern decomposes a collection into two collections.

Instances
Matcher m a => CollectionPat (Set m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

nil :: Matcher (Set m) [a] => Pattern [a] (Set m) ctx [] Source #

cons :: (Matcher (Set m) [a], [a] ~ [a'], Set m ~ f m') => Pattern a' m' ctx xs -> Pattern [a] (Set m) (ctx :++: xs) ys -> Pattern [a] (Set m) ctx (xs :++: ys) Source #

join :: Matcher (Set m) [a] => Pattern [a] (Set m) ctx xs -> Pattern [a] (Set m) (ctx :++: xs) ys -> Pattern [a] (Set m) ctx (xs :++: ys) Source #

Matcher m a => CollectionPat (Multiset m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

nil :: Matcher (Multiset m) [a] => Pattern [a] (Multiset m) ctx [] Source #

cons :: (Matcher (Multiset m) [a], [a] ~ [a'], Multiset m ~ f m') => Pattern a' m' ctx xs -> Pattern [a] (Multiset m) (ctx :++: xs) ys -> Pattern [a] (Multiset m) ctx (xs :++: ys) Source #

join :: Matcher (Multiset m) [a] => Pattern [a] (Multiset m) ctx xs -> Pattern [a] (Multiset m) (ctx :++: xs) ys -> Pattern [a] (Multiset m) ctx (xs :++: ys) Source #

Matcher m a => CollectionPat (List m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

nil :: Matcher (List m) [a] => Pattern [a] (List m) ctx [] Source #

cons :: (Matcher (List m) [a], [a] ~ [a'], List m ~ f m') => Pattern a' m' ctx xs -> Pattern [a] (List m) (ctx :++: xs) ys -> Pattern [a] (List m) ctx (xs :++: ys) Source #

join :: Matcher (List m) [a] => Pattern [a] (List m) ctx xs -> Pattern [a] (List m) (ctx :++: xs) ys -> Pattern [a] (List m) ctx (xs :++: ys) Source #

newtype List m Source #

A matcher for a list.

Constructors

List m 
Instances
Matcher m a => Matcher (List m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher m a => CollectionPat (List m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

nil :: Matcher (List m) [a] => Pattern [a] (List m) ctx [] Source #

cons :: (Matcher (List m) [a], [a] ~ [a'], List m ~ f m') => Pattern a' m' ctx xs -> Pattern [a] (List m) (ctx :++: xs) ys -> Pattern [a] (List m) ctx (xs :++: ys) Source #

join :: Matcher (List m) [a] => Pattern [a] (List m) ctx xs -> Pattern [a] (List m) (ctx :++: xs) ys -> Pattern [a] (List m) ctx (xs :++: ys) Source #

(Matcher m a, Eq a, ValuePat m a) => ValuePat (List m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher (List m) [a], Eq [a]) => (HList ctx -> [a]) -> Pattern [a] (List m) ctx [] Source #

newtype Multiset m Source #

A matcher for a multiset. When we regard a collection as a multiset, the order of elements is ignored but the number of times an element appears in the collection is counted.

Constructors

Multiset m 
Instances
Matcher m a => Matcher (Multiset m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher m a => CollectionPat (Multiset m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

nil :: Matcher (Multiset m) [a] => Pattern [a] (Multiset m) ctx [] Source #

cons :: (Matcher (Multiset m) [a], [a] ~ [a'], Multiset m ~ f m') => Pattern a' m' ctx xs -> Pattern [a] (Multiset m) (ctx :++: xs) ys -> Pattern [a] (Multiset m) ctx (xs :++: ys) Source #

join :: Matcher (Multiset m) [a] => Pattern [a] (Multiset m) ctx xs -> Pattern [a] (Multiset m) (ctx :++: xs) ys -> Pattern [a] (Multiset m) ctx (xs :++: ys) Source #

(Matcher m a, Eq a, ValuePat m a) => ValuePat (Multiset m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher (Multiset m) [a], Eq [a]) => (HList ctx -> [a]) -> Pattern [a] (Multiset m) ctx [] Source #

newtype Set m Source #

A matcher for a set. Both the order and the repetition of elements are ignored.

Constructors

Set m 
Instances
Matcher m a => Matcher (Set m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher m a => CollectionPat (Set m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

nil :: Matcher (Set m) [a] => Pattern [a] (Set m) ctx [] Source #

cons :: (Matcher (Set m) [a], [a] ~ [a'], Set m ~ f m') => Pattern a' m' ctx xs -> Pattern [a] (Set m) (ctx :++: xs) ys -> Pattern [a] (Set m) ctx (xs :++: ys) Source #

join :: Matcher (Set m) [a] => Pattern [a] (Set m) ctx xs -> Pattern [a] (Set m) (ctx :++: xs) ys -> Pattern [a] (Set m) ctx (xs :++: ys) Source #

(Matcher m a, Eq a, Ord a, ValuePat m a) => ValuePat (Set m) [a] Source # 
Instance details

Defined in Control.Egison.Matcher

Methods

valuePat :: (Matcher (Set m) [a], Eq [a]) => (HList ctx -> [a]) -> Pattern [a] (Set m) ctx [] Source #