kleene-0.1: Kleene algebra

Safe HaskellSafe
LanguageHaskell2010

Kleene.Functor

Contents

Synopsis

Documentation

data K c a Source #

Applicative Functor regular expression.

Instances
Functor (K c) Source # 
Instance details

Defined in Kleene.Internal.Functor

Methods

fmap :: (a -> b) -> K c a -> K c b #

(<$) :: a -> K c b -> K c a #

Applicative (K c) Source # 
Instance details

Defined in Kleene.Internal.Functor

Methods

pure :: a -> K c a #

(<*>) :: K c (a -> b) -> K c a -> K c b #

liftA2 :: (a -> b -> c0) -> K c a -> K c b -> K c c0 #

(*>) :: K c a -> K c b -> K c b #

(<*) :: K c a -> K c b -> K c a #

Alternative (K c) Source # 
Instance details

Defined in Kleene.Internal.Functor

Methods

empty :: K c a #

(<|>) :: K c a -> K c a -> K c a #

some :: K c a -> K c [a] #

many :: K c a -> K c [a] #

Alt (K c) Source # 
Instance details

Defined in Kleene.Internal.Functor

Methods

(<!>) :: K c a -> K c a -> K c a #

some :: Applicative (K c) => K c a -> K c [a] #

many :: Applicative (K c) => K c a -> K c [a] #

Apply (K c) Source # 
Instance details

Defined in Kleene.Internal.Functor

Methods

(<.>) :: K c (a -> b) -> K c a -> K c b #

(.>) :: K c a -> K c b -> K c b #

(<.) :: K c a -> K c b -> K c a #

liftF2 :: (a -> b -> c0) -> K c a -> K c b -> K c c0 #

(c ~ Char, IsString a) => IsString (K c a) Source # 
Instance details

Defined in Kleene.Internal.Functor

Methods

fromString :: String -> K c a #

c ~ Char => Pretty (K c a) Source #

Convert to non-matching JavaScript string which can be used as an argument to new RegExp

>>> putPretty ("foobar" :: K Char String)
^foobar$
>>> putPretty $ many ("foobar" :: K Char String)
^(foobar)*$
Instance details

Defined in Kleene.Internal.Functor

Methods

pretty :: K c a -> String Source #

prettyS :: K c a -> ShowS Source #

Constructors

few :: K c a -> K c [a] Source #

few, not many.

Let's define two similar regexps

>>> let re1 = liftA2 (,) (few  $ char 'a') (many $ char 'a')
>>> let re2 = liftA2 (,) (many $ char 'a') (few  $ char 'a')

Their RE behaviour is the same:

>>> C.equivalent (toRE re1) (toRE re2)
True
>>> map (C.match $ toRE re1) ["aaa","bbb"]
[True,False]

However, the RA behaviour is different!

>>> R.match (toRA re1) "aaaa"
Just ("","aaaa")
>>> R.match (toRA re2) "aaaa"
Just ("aaaa","")

anyChar :: (Ord c, Enum c, Bounded c) => K c c Source #

>>> putPretty anyChar
^[^]$

oneof :: (Ord c, Enum c, Foldable f) => f c -> K c c Source #

>>> putPretty $ oneof ("foobar" :: [Char])
^[a-bfor]$

char :: (Ord c, Enum c) => c -> K c c Source #

>>> putPretty $ char 'x'
^x$

charRange :: (Enum c, Ord c) => c -> c -> K c c Source #

>>> putPretty $ charRange 'a' 'z'
^[a-z]$

dot :: K Char Char Source #

>>> putPretty dot
^.$

everything :: (Ord c, Enum c, Bounded c) => K c [c] Source #

>>> putPretty everything
^[^]*$

everything1 :: (Ord c, Enum c, Bounded c) => K c [c] Source #

>>> putPretty everything1
^[^][^]*$

Queries

isEmpty :: (Ord c, Enum c, Bounded c) => K c a -> Bool Source #

Matches nothing?

isEverything :: (Ord c, Enum c, Bounded c) => K c a -> Bool Source #

Matches whole input?

Matching

match :: K c a -> [c] -> Maybe a Source #

Match using regex-applicative

Conversions

toRE :: (Ord c, Enum c, Bounded c) => K c a -> RE c Source #

Convert to RE.

>>> putPretty (toRE $ many "foo" :: RE.RE Char)
^(foo)*$

toKleene :: FiniteKleene c k => K c a -> k Source #

Convert to any Kleene

fromRE :: (Ord c, Enum c) => RE c -> K c [c] Source #

Convert from RE.

Note: all REStars are converted to Greedy ones, it doesn't matter, as we don't capture anything.

>>> match (fromRE "foobar") "foobar"
Just "foobar"
>>> match (fromRE $ C.star "a" <> C.star "a") "aaaa"
Just "aaaa"

toRA :: K c a -> RE c a Source #

Convert K to RE from regex-applicative.

>>> R.match (toRA ("xx" *> everything <* "zz" :: K Char String)) "xxyyyzz"
Just "yyy"

See also match.