Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data M c
- empty :: M c
- eps :: M c
- char :: c -> M c
- charRange :: Enum c => c -> c -> M c
- anyChar :: (Bounded c, Enum c) => M c
- appends :: [M c] -> M c
- unions :: [M c] -> M c
- star :: M c -> M c
- string :: [c] -> M c
- nullable :: M c -> Bool
- derivate :: (Eq c, Enum c, Bounded c) => c -> M c -> M c
- generate :: Int -> M c -> [[c]]
- toKleene :: CharKleene c k => M c -> k
- isEmpty :: M c -> Bool
- isEps :: M c -> Bool
Documentation
Regular expression which has no restrictions on the elements.
Therefore we can have Monad
instance, i.e. have a regexp where
characters are regexps themselves.
Because there are no optimisations, it's better to work over small alphabets. On the other hand, we can work over infinite alphabets, if we only use small amount of symbols!
>>>
putPretty $ string [True, False]
^10$
>>>
let re = string [True, False, True]
>>>
let re' = re >>= \b -> if b then char () else star (char ())
>>>
putPretty re'
^..*.$
MChars [c] | One of the characters |
MAppend [M c] | Concatenation |
MUnion [c] [M c] | Union |
MStar (M c) | Kleene star |
Instances
Monad M Source # | |
Functor M Source # | |
Applicative M Source # | |
Foldable M Source # | |
Defined in Kleene.Monad fold :: Monoid m => M m -> m # foldMap :: Monoid m => (a -> m) -> M a -> m # foldr :: (a -> b -> b) -> b -> M a -> b # foldr' :: (a -> b -> b) -> b -> M a -> b # foldl :: (b -> a -> b) -> b -> M a -> b # foldl' :: (b -> a -> b) -> b -> M a -> b # foldr1 :: (a -> a -> a) -> M a -> a # foldl1 :: (a -> a -> a) -> M a -> a # elem :: Eq a => a -> M a -> Bool # maximum :: Ord a => M a -> a # | |
Traversable M Source # | |
(Eq c, Enum c, Bounded c) => Match c (M c) Source # | |
(Eq c, Enum c, Bounded c) => Derivate c (M c) Source # | |
CharKleene c (M c) Source # | |
Eq c => Eq (M c) Source # | |
Ord c => Ord (M c) Source # | |
Show c => Show (M c) Source # | |
c ~ Char => IsString (M c) Source # | |
Defined in Kleene.Monad fromString :: String -> M c # | |
Semigroup (M c) Source # | |
Monoid (M c) Source # | |
(Eq c, Enum c, Bounded c, Arbitrary c) => Arbitrary (M c) Source # | |
CoArbitrary c => CoArbitrary (M c) Source # | |
Defined in Kleene.Monad coarbitrary :: M c -> Gen b -> Gen b # | |
(Pretty c, Eq c) => Pretty (M c) Source # | |
Kleene (M c) Source # | |
Construction
Empty regex. Doesn't accept anything.
>>>
putPretty (empty :: M Bool)
^[]$
match (empty :: M Char) (s :: String) === False
Empty string. Note: different than empty
.
>>>
putPretty (eps :: M Bool)
^$
>>>
putPretty (mempty :: M Bool)
^$
match (eps :: M Char) s === null (s :: String)
charRange :: Enum c => c -> c -> M c Source #
Note: we know little about c
.
>>>
putPretty $ charRange 'a' 'z'
^[abcdefghijklmnopqrstuvwxyz]$
anyChar :: (Bounded c, Enum c) => M c Source #
Any character. Note: different than dot!
>>>
putPretty (anyChar :: M Bool)
^[01]$
Literal string.
>>>
putPretty ("foobar" :: M Char)
^foobar$
>>>
putPretty ("(.)" :: M Char)
^\(\.\)$
>>>
putPretty $ string [False, True]
^01$
Derivative
nullable :: M c -> Bool Source #
We say that a regular expression r is nullable if the language it defines contains the empty string.
>>>
nullable eps
True
>>>
nullable (star "x")
True
>>>
nullable "foo"
False
derivate :: (Eq c, Enum c, Bounded c) => c -> M c -> M c Source #
Intuitively, the derivative of a language \(\mathcal{L} \subset \Sigma^\star\) with respect to a symbol \(a \in \Sigma\) is the language that includes only those suffixes of strings with a leading symbol \(a\) in \(\mathcal{L}\).
>>>
putPretty $ derivate 'f' "foobar"
^oobar$
>>>
putPretty $ derivate 'x' $ unions ["xyz", "abc"]
^yz$
>>>
putPretty $ derivate 'x' $ star "xyz"
^yz(xyz)*$
Generation
Generate random strings of the language M c
describes.
>>>
let example = traverse_ print . take 3 . generate 42
>>>
example "abc"
"abc" "abc" "abc"
>>>
example $ star $ unions ["a", "b"]
"ababbb" "baab" "abbababaa"
xx >>> example empty
expensive-prop> all (match r) $ take 10 $ generate 42 (r :: M Bool)
Conversion
toKleene :: CharKleene c k => M c -> k Source #
Convert to Kleene
>>>
let re = charRange 'a' 'z'
>>>
putPretty re
^[abcdefghijklmnopqrstuvwxyz]$
>>>
putPretty (toKleene re :: RE Char)
^[a-z]$