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

Safe HaskellSafe
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 => (HList ctx -> m -> a -> [MList ctx vs]) -> Pattern a m ctx vs 

class Matcher a Source #

Instances
Matcher Integer Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher Eql Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher Something Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher a => Matcher (Set a) Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher a => Matcher (Multiset a) Source # 
Instance details

Defined in Control.Egison.Matcher

Matcher a => Matcher (List a) Source # 
Instance details

Defined in Control.Egison.Matcher

(Matcher a, Matcher b) => Matcher (Pair a b) Source # 
Instance details

Defined in Control.Egison.Matcher

data MatchClause a m b Source #

Constructors

Matcher m => 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 => 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) 

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

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