Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- class (BoundedJoinSemiLattice k, Semigroup k, Monoid k) => Kleene c k | k -> c where
- oneof :: (Kleene c k, Foldable f) => f c -> k
- class Kleene c k => FiniteKleene c k | k -> c where
- class Derivate c k | k -> c where
- class Match c k | k -> c where
- class Match c k => Equivalent c k | k -> c where
- class Derivate c k => TransitionMap c k | k -> c where
- class Complement c k | k -> c where
Documentation
class (BoundedJoinSemiLattice k, Semigroup k, Monoid k) => Kleene c k | k -> c where Source #
Empty regex. Doesn't accept anything.
Empty string. Note: different than empty
Single character
Concatenation.
Union.
Kleene star
class Kleene c k => FiniteKleene c k | k -> c where Source #
class Match c k | k -> c where Source #
An f
can be used to match on the input.
(Ord c, Enum c) => Match c (ERE c) Source # | |
(Eq c, Enum c, Bounded c) => Match c (M c) Source # | |
(Ord c, Enum c, Bounded c) => Match c (RE c) Source # | |
Ord c => Match c (DFA c) Source # | Run Because we have analysed a language, in some cases we can determine an input
without traversing all of the input.
That's not the cases with
Holds:
all (match (fromRE r)) $ take 10 $ RE.generate (curry QC.choose) 42 (r :: RE.RE Char) |
Match c (r c) => Match c (Equiv r c) Source # | |
class Match c k => Equivalent c k | k -> c where Source #
equivalent :: k -> k -> Bool Source #
(Ord c, Enum c, Bounded c) => Equivalent c (ERE c) Source # | |
(Ord c, Enum c, Bounded c) => Equivalent c (RE c) Source # | |
Equivalent c (r c) => Equivalent c (Equiv r c) Source # | |
class Derivate c k => TransitionMap c k | k -> c where Source #
Transition map.
transitionMap :: k -> Map k (SF c k) Source #
class Complement c k | k -> c where Source #
complement :: k -> k Source #
Complement c (ERE c) Source # | |
Complement c (DFA c) Source # | Complement DFA. Complement of
|
Complement c (r c) => Complement c (Equiv r c) Source # | |