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

Safe HaskellNone
LanguageHaskell2010

Control.Egison.Core

Documentation

data Pattern a m ctx vs where Source #

Constructors

Wildcard :: Pattern a m ctx '[] 
PatVar :: String -> Pattern a m ctx '[a] 
AndPat :: Pattern a m ctx vs -> Pattern a m (ctx :++: vs) vs' -> Pattern a m ctx (vs :++: vs') 
OrPat :: Pattern a m ctx vs -> Pattern a m ctx vs -> Pattern a m ctx vs 
NotPat :: Pattern a m ctx '[] -> Pattern a m ctx '[] 
PredicatePat :: (HList ctx -> a -> Bool) -> Pattern a m ctx '[] 
Pattern :: Matcher m a => (HList ctx -> m -> a -> [MList ctx vs]) -> Pattern a m ctx vs 

class Matcher m a Source #

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

Defined in Control.Egison.Matcher

Matcher Eql a Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher Something a Source # 
Instance details

Defined in Control.Egison.Matcher

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

Defined in Control.Egison.Matcher

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

Defined in Control.Egison.Matcher

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

Defined in Control.Egison.Matcher

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

Defined in Control.Egison.Matcher

data MatchClause a m b Source #

Constructors

Matcher m a => MatchClause (Pattern a m '[] vs) (HList vs -> b) 

data MState vs where Source #

Constructors

MState :: vs ~ (xs :++: ys) => HList xs -> MList xs ys -> MState vs 

data MAtom ctx vs Source #

Constructors

Matcher m a => MAtom (Pattern a m ctx vs) m a 

data MList ctx vs where Source #

Constructors

MNil :: MList ctx '[] 
MCons :: MAtom ctx xs -> MList (ctx :++: xs) ys -> MList ctx (xs :++: ys) 
MJoin :: MList ctx xs -> MList (ctx :++: xs) ys -> MList ctx (xs :++: ys) 

mappend :: MList ctx xs -> MList (ctx :++: xs) ys -> MList ctx (xs :++: ys) Source #

oneMAtom :: MAtom ctx xs -> MList ctx xs Source #

twoMAtoms :: MAtom ctx xs -> MAtom (ctx :++: xs) ys -> MList ctx (xs :++: ys) Source #

threeMAtoms :: MAtom ctx xs -> MAtom (ctx :++: xs) ys -> MAtom ((ctx :++: xs) :++: ys) zs -> MList ctx ((xs :++: ys) :++: zs) Source #

data HList xs where Source #

Constructors

HNil :: HList '[] 
HCons :: a -> HList as -> HList (a ': as) 

happend :: HList as -> HList bs -> HList (as :++: bs) Source #

type family (as :: [*]) :++: (bs :: [*]) :: [*] where ... Source #

Equations

as :++: '[] = as 
'[] :++: bs = bs 
(a ': as) :++: bs = a ': (as :++: bs)