kleene-0.1: Kleene algebra

Safe HaskellSafe
LanguageHaskell2010

Kleene.Functor.NonEmpty

Contents

Synopsis

Documentation

data K1 c a Source #

Applicative Functor regular expression.

Instances
Functor (K1 c) Source # 
Instance details

Defined in Kleene.Functor.NonEmpty

Methods

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

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

Alt (K1 c) Source # 
Instance details

Defined in Kleene.Functor.NonEmpty

Methods

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

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

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

Apply (K1 c) Source # 
Instance details

Defined in Kleene.Functor.NonEmpty

Methods

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

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

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

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

c ~ Char => Pretty (K1 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.Functor.NonEmpty

Methods

pretty :: K1 c a -> String Source #

prettyS :: K1 c a -> ShowS Source #

Constructors

some1 :: K1 c a -> K1 c (NonEmpty a) Source #

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

>>> putPretty anyChar
^[^]$

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

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

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

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

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

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

dot :: K1 Char Char Source #

>>> putPretty dot
^.$

everything1 :: (Ord c, Enum c, Bounded c) => K1 c (NonEmpty c) Source #

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

Queries

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

Matches nothing?

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

Matches whole input?

Matching

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

Match using regex-applicative

Conversions

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

Convert to RE.

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

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

Convert to any Kleene

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

Convert K to RE from regex-applicative.

>>> R.match (toRA (string "xx" .> everything1 <. string "zz" :: K1 Char (NonEmpty Char))) "xxyyzyyzz"
Just ('y' :| "yzyy")

See also match.

nullableProof :: K c a -> Either (K1 c a) (a, K1 c a) Source #

>>> putPretty $ nullableProof (pure True)
Right 1 , ^[]$
>>> putPretty $ nullableProof (many "xyz" :: K Char [String])
Right [] , ^xyz(xyz)*$
>>> putPretty $ nullableProof (many $ toList <$> optional "x" <|> many "yz" :: K Char [[String]])
Right [] , ^(x|yz(yz)*)(x|yz(yz)*)*$