module Data.Flex.Examples.Lex.Simple where data Basic c = BSimple c -- | range | set | ... deriving Show data BSingle b = SSimple b | b `SOr` BSingle b deriving Show infixr 9 `SOr` type Single c = BSingle (Basic c) data Simple f c = TSimple { simpleSingle :: (Single c) ,simpleNext :: f } deriving Show newtype Once f c = SOnce {unSOnce :: Simple f c} deriving Show newtype Repeat f c = SRepeat {unSRepeat :: Simple f c} deriving Show data Lex c a = LNil | LDone a | LRepeat (Repeat (Lex c a) c) | Once (Lex c a) c `LOr` Lex c a deriving Show infixr 9 `LOr` type DiffList c = [c] -> [c] singleMatch :: Eq c => Single c -> c -> Bool singleMatch (SSimple c1) c2 = basicMatch c1 c2 singleMatch (s1 `SOr` s2) c = basicMatch s1 c || singleMatch s2 c basicMatch :: Eq c => Basic c -> c -> Bool basicMatch (BSimple c1) c2 = c1 == c2 -- vim: expandtab:tabstop=4:shiftwidth=4