kleene-0.1: Kleene algebra

Safe HaskellSafe
LanguageHaskell2010

Kleene.Monad

Contents

Synopsis

Documentation

data M c Source #

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'
^..*.$

Constructors

MChars [c]

One of the characters

MAppend [M c]

Concatenation

MUnion [c] [M c]

Union

MStar (M c)

Kleene star

Instances
Monad M Source # 
Instance details

Defined in Kleene.Monad

Methods

(>>=) :: M a -> (a -> M b) -> M b #

(>>) :: M a -> M b -> M b #

return :: a -> M a #

fail :: String -> M a #

Functor M Source # 
Instance details

Defined in Kleene.Monad

Methods

fmap :: (a -> b) -> M a -> M b #

(<$) :: a -> M b -> M a #

Applicative M Source # 
Instance details

Defined in Kleene.Monad

Methods

pure :: a -> M a #

(<*>) :: M (a -> b) -> M a -> M b #

liftA2 :: (a -> b -> c) -> M a -> M b -> M c #

(*>) :: M a -> M b -> M b #

(<*) :: M a -> M b -> M a #

Foldable M Source # 
Instance details

Defined in Kleene.Monad

Methods

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 #

toList :: M a -> [a] #

null :: M a -> Bool #

length :: M a -> Int #

elem :: Eq a => a -> M a -> Bool #

maximum :: Ord a => M a -> a #

minimum :: Ord a => M a -> a #

sum :: Num a => M a -> a #

product :: Num a => M a -> a #

Traversable M Source # 
Instance details

Defined in Kleene.Monad

Methods

traverse :: Applicative f => (a -> f b) -> M a -> f (M b) #

sequenceA :: Applicative f => M (f a) -> f (M a) #

mapM :: Monad m => (a -> m b) -> M a -> m (M b) #

sequence :: Monad m => M (m a) -> m (M a) #

(Eq c, Enum c, Bounded c) => Match c (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

match :: M c -> [c] -> Bool Source #

match8 :: M c -> ByteString -> Bool Source #

(Eq c, Enum c, Bounded c) => Derivate c (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

nullable :: M c -> Bool Source #

derivate :: c -> M c -> M c Source #

CharKleene c (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

char :: c -> M c Source #

string :: [c] -> M c Source #

Eq c => Eq (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

(==) :: M c -> M c -> Bool #

(/=) :: M c -> M c -> Bool #

Ord c => Ord (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

compare :: M c -> M c -> Ordering #

(<) :: M c -> M c -> Bool #

(<=) :: M c -> M c -> Bool #

(>) :: M c -> M c -> Bool #

(>=) :: M c -> M c -> Bool #

max :: M c -> M c -> M c #

min :: M c -> M c -> M c #

Show c => Show (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

showsPrec :: Int -> M c -> ShowS #

show :: M c -> String #

showList :: [M c] -> ShowS #

c ~ Char => IsString (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

fromString :: String -> M c #

Semigroup (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

(<>) :: M c -> M c -> M c #

sconcat :: NonEmpty (M c) -> M c #

stimes :: Integral b => b -> M c -> M c #

Monoid (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

mempty :: M c #

mappend :: M c -> M c -> M c #

mconcat :: [M c] -> M c #

(Eq c, Enum c, Bounded c, Arbitrary c) => Arbitrary (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

arbitrary :: Gen (M c) #

shrink :: M c -> [M c] #

CoArbitrary c => CoArbitrary (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

coarbitrary :: M c -> Gen b -> Gen b #

(Pretty c, Eq c) => Pretty (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

pretty :: M c -> String Source #

prettyS :: M c -> ShowS Source #

Kleene (M c) Source # 
Instance details

Defined in Kleene.Monad

Methods

empty :: M c Source #

eps :: M c Source #

appends :: [M c] -> M c Source #

unions :: [M c] -> M c Source #

star :: M c -> M c Source #

Construction

Binary operators are

  • <> for append

There are no binary operator for union. Use unions.

empty :: M c Source #

Empty regex. Doesn't accept anything.

>>> putPretty (empty :: M Bool)
^[]$
match (empty :: M Char) (s :: String) === False

eps :: M c Source #

Empty string. Note: different than empty.

>>> putPretty (eps :: M Bool)
^$
>>> putPretty (mempty :: M Bool)
^$
match (eps :: M Char) s === null (s :: String)

char :: c -> M c Source #

>>> putPretty (char 'x')
^x$

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]$

appends :: [M c] -> M c Source #

Concatenate regular expressions.

unions :: [M c] -> M c Source #

Union of regular expressions.

Lattice laws don't hold structurally:

star :: M c -> M c Source #

Kleene star.

string :: [c] -> M c Source #

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 Source #

Arguments

:: Int

seed

-> M c 
-> [[c]]

infinite list of results

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]$

Other

isEmpty :: M c -> Bool Source #

Whether M is (structurally) equal to empty.

isEps :: M c -> Bool Source #

Whether M is (structurally) equal to eps.