kleene-0: Kleene algebra

Safe HaskellSafe
LanguageHaskell2010

Kleene

Contents

Description

Kleene algebra.

This package provides means to work with kleene algebra, at the moment specifically concentrating on regular expressions over Char.

Implements ideas from Regular-expression derivatives re-examined by Scott Owens, John Reppy and Aaron Turon https://doi.org/10.1017/S0956796808007090.

>>> :set -XOverloadedStrings
>>> import Algebra.Lattice
>>> import Algebra.PartialOrd
>>> import Data.Semigroup
>>> import Kleene.Internal.Pretty (putPretty)

Kleene.RE module provides RE type. Kleene.Classes module provides various classes to work with the type. All of that is re-exported from Kleene module.

First let's construct a regular expression value:

>>> let re = star "abc" <> "def" <> ("x" \/ "yz") :: RE Char
>>> putPretty re
^(abc)*def(x|yz)$

We can convert it to DFA (there are 8 states)

>>> putPretty $ fromTM re
0 -> \x -> if
    | x <= '`'  -> 8
    | x <= 'a'  -> 5
    | x <= 'c'  -> 8
    | x <= 'd'  -> 3
    | otherwise -> 8
1 -> \x -> if
    | x <= 'w'  -> 8
    | x <= 'x'  -> 6
    | x <= 'y'  -> 7
    | otherwise -> 8
2 -> ...
...

And we can convert back from DFA to RE:

>>> let re' = toKleene (fromTM re) :: RE Char
>>> putPretty re'
^(a(bca)*bcdefx|defx|(a(bca)*bcdefy|defy)z)$

As you see, we don't get what we started with. Yet, these regular expressions are equivalent;

>>> equivalent re re'
True

or using Equiv wrapper

>>> Equiv re == Equiv re'
True

(The paper doesn't outline decision procedure for the equivalence, though it's right there - seems to be fast enough at least for toy examples like here).

We can use regular expressions to generate word examples in the language:

>>> import Data.Foldable
>>> import qualified Test.QuickCheck as QC
>>> import Kleene.RE (generate)
>>> traverse_ print $ take 5 $ generate (curry QC.choose) 42 re
"abcabcabcabcabcabcdefyz"
"abcabcabcabcdefyz"
"abcabcabcabcabcabcabcabcabcdefx"
"abcabcdefx"
"abcabcabcabcabcabcdefyz"

In addition to the "normal" regular expressions, there are extended regular expressions. Regular expressions which we can complement, and therefore intersect:

>>> let ere = star "aa" /\ star "aaa" :: ERE Char
>>> putPretty ere
^~(~((aa)*)|~((aaa)*))$

We can convert ERE to RE via DFA:

>>> let re'' = toKleene (fromTM ere) :: RE Char
>>> putPretty re''
^(a(aaaaaa)*aaaaa)?$

Machine works own ways, we don't (always) get as pretty results as we'd like:

>>> equivalent re'' (star "aaaaaa")
True

Another feature of the library is an Applciative Functor,

>>> import Control.Applicative
>>> import qualified Kleene.Functor as F
>>> let f = (,) <$> many (F.char 'x') <* F.few F.anyChar <*> many (F.char 'z')
>>> putPretty f
^x*[^]*z*$

By relying on http://hackage.haskell.org/package/regex-applicative library, we can match and capture with regular expression.

>>> F.match f "xyyzzz"
Just ("x","zzz")

Where with RE we can only get True or False:

>>> match (F.toRE f) "xyyzzz"
True

Which in this case is not even interesting because:

>>> equivalent (F.toRE f) everything
True

Converting from RE to K is also possible, which may be handy:

>>> let g = (,) <$> F.few F.anyChar <*> F.fromRE re''
>>> putPretty g
^[^]*(a(aaaaaa)*aaaaa)?$
>>> F.match g (replicate 20 'a')
Just ("aa","aaaaaaaaaaaaaaaaaa")

We got longest divisible by 6 prefix of as. That's because fromRE uses many for star.

Synopsis

Regular expressions

data RE c Source #

Regular expression

Constructors are exposed, but you should use smart constructors in this module to construct RE.

The Eq and Ord instances are structural. The Kleene etc constructors do "weak normalisation", so for values constructed using those operations Eq witnesses "weak equivalence". See equivalent for regular-expression equivalence.

Structure is exposed in Kleene.RE module but consider constructors as half-internal. There are soft-invariants, but violating them shouldn't break anything in the package. (e.g. transitionMap will eventually terminate, but may create more redundant states if starting regexp is not "weakly normalised").

Instances

(Ord c, Enum c, Bounded c) => TransitionMap c (RE c) Source # 

Methods

transitionMap :: RE c -> Map (RE c) (SF c (RE c)) Source #

(Ord c, Enum c, Bounded c) => Equivalent c (RE c) Source # 

Methods

equivalent :: RE c -> RE c -> Bool Source #

(Ord c, Enum c, Bounded c) => Match c (RE c) Source # 

Methods

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

(Ord c, Enum c, Bounded c) => Derivate c (RE c) Source # 

Methods

nullable :: RE c -> Bool Source #

derivate :: c -> RE c -> RE c Source #

(Ord c, Enum c, Bounded c) => FiniteKleene c (RE c) Source # 

Methods

everything :: RE c Source #

charRange :: c -> c -> RE c Source #

fromRSet :: RSet c -> RE c Source #

dot :: RE c Source #

anyChar :: RE c Source #

(Ord c, Enum c, Bounded c) => Kleene c (RE c) Source # 

Methods

empty :: RE c Source #

eps :: RE c Source #

char :: c -> RE c Source #

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

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

star :: RE c -> RE c Source #

Eq c => Eq (RE c) Source # 

Methods

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

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

Ord c => Ord (RE c) Source # 

Methods

compare :: RE c -> RE c -> Ordering #

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

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

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

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

max :: RE c -> RE c -> RE c #

min :: RE c -> RE c -> RE c #

Show c => Show (RE c) Source # 

Methods

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

show :: RE c -> String #

showList :: [RE c] -> ShowS #

(~) * c Char => IsString (RE c) Source # 

Methods

fromString :: String -> RE c #

Eq c => Semigroup (RE c) Source # 

Methods

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

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

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

Eq c => Monoid (RE c) Source # 

Methods

mempty :: RE c #

mappend :: RE c -> RE c -> RE c #

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

(Ord c, Enum c, Bounded c, Arbitrary c) => Arbitrary (RE c) Source # 

Methods

arbitrary :: Gen (RE c) #

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

CoArbitrary c => CoArbitrary (RE c) Source # 

Methods

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

(Ord c, Enum c, Bounded c) => JoinSemiLattice (RE c) Source # 

Methods

(\/) :: RE c -> RE c -> RE c #

join :: RE c -> RE c -> RE c #

(Ord c, Enum c, Bounded c) => BoundedJoinSemiLattice (RE c) Source # 

Methods

bottom :: RE c #

(~) * c Char => Pretty (RE c) Source # 

Methods

pretty :: RE c -> String Source #

prettyS :: RE c -> ShowS Source #

data ERE c Source #

Extended regular expression

It's both, Kleene and Boolean algebra. (If we add only intersections, it wouldn't be Boolean).

Note: we don't have special constructor for intersections. We use de Morgan formula \(a \land b = \neg (\neg a \lor \neg b)\).

>>> putPretty $ asEREChar $ "a" /\ "b"
^~(~a|~b)$

There is no generator, as intersections makes it hard.

Instances

Complement c (ERE c) Source # 

Methods

complement :: ERE c -> ERE c Source #

(Ord c, Enum c, Bounded c) => TransitionMap c (ERE c) Source # 

Methods

transitionMap :: ERE c -> Map (ERE c) (SF c (ERE c)) Source #

(Ord c, Enum c, Bounded c) => Equivalent c (ERE c) Source # 

Methods

equivalent :: ERE c -> ERE c -> Bool Source #

(Ord c, Enum c) => Match c (ERE c) Source # 

Methods

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

(Ord c, Enum c) => Derivate c (ERE c) Source # 

Methods

nullable :: ERE c -> Bool Source #

derivate :: c -> ERE c -> ERE c Source #

(Ord c, Enum c, Bounded c) => FiniteKleene c (ERE c) Source # 

Methods

everything :: ERE c Source #

charRange :: c -> c -> ERE c Source #

fromRSet :: RSet c -> ERE c Source #

dot :: ERE c Source #

anyChar :: ERE c Source #

(Ord c, Enum c, Bounded c) => Kleene c (ERE c) Source # 

Methods

empty :: ERE c Source #

eps :: ERE c Source #

char :: c -> ERE c Source #

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

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

star :: ERE c -> ERE c Source #

Eq c => Eq (ERE c) Source # 

Methods

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

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

Ord c => Ord (ERE c) Source # 

Methods

compare :: ERE c -> ERE c -> Ordering #

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

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

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

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

max :: ERE c -> ERE c -> ERE c #

min :: ERE c -> ERE c -> ERE c #

Show c => Show (ERE c) Source # 

Methods

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

show :: ERE c -> String #

showList :: [ERE c] -> ShowS #

(~) * c Char => IsString (ERE c) Source # 

Methods

fromString :: String -> ERE c #

Eq c => Semigroup (ERE c) Source # 

Methods

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

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

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

Eq c => Monoid (ERE c) Source # 

Methods

mempty :: ERE c #

mappend :: ERE c -> ERE c -> ERE c #

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

(Ord c, Enum c, Bounded c, Arbitrary c) => Arbitrary (ERE c) Source # 

Methods

arbitrary :: Gen (ERE c) #

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

CoArbitrary c => CoArbitrary (ERE c) Source # 

Methods

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

(Ord c, Enum c) => JoinSemiLattice (ERE c) Source # 

Methods

(\/) :: ERE c -> ERE c -> ERE c #

join :: ERE c -> ERE c -> ERE c #

(Ord c, Enum c) => MeetSemiLattice (ERE c) Source # 

Methods

(/\) :: ERE c -> ERE c -> ERE c #

meet :: ERE c -> ERE c -> ERE c #

(Ord c, Enum c) => Lattice (ERE c) Source # 
(Ord c, Enum c) => BoundedJoinSemiLattice (ERE c) Source # 

Methods

bottom :: ERE c #

(Ord c, Enum c) => BoundedMeetSemiLattice (ERE c) Source # 

Methods

top :: ERE c #

(Ord c, Enum c) => BoundedLattice (ERE c) Source # 
(~) * c Char => Pretty (ERE c) Source # 

Methods

pretty :: ERE c -> String Source #

prettyS :: ERE c -> ShowS Source #

Equivalance (and partial order)

newtype Equiv r c Source #

Regular-expressions for which == is equivalent.

>>> let re1 = star "a" <> "a" :: RE Char
>>> let re2 = "a" <> star "a" :: RE Char
>>> re1 == re2
False
>>> Equiv re1 == Equiv re2
True

Equiv is also a PartialOrd (but not Ord!)

>>> Equiv "a" `leq` Equiv (star "a" :: RE Char)
True

Not all regular expessions are comparable:

>>> let reA = Equiv "a" :: Equiv RE Char
>>> let reB = Equiv "b" :: Equiv RE Char
>>> (leq reA reB, leq reB reA)
(False,False)

Constructors

Equiv (r c) 

Instances

Complement c (r c) => Complement c (Equiv r c) Source # 

Methods

complement :: Equiv r c -> Equiv r c Source #

Equivalent c (r c) => Equivalent c (Equiv r c) Source # 

Methods

equivalent :: Equiv r c -> Equiv r c -> Bool Source #

Match c (r c) => Match c (Equiv r c) Source # 

Methods

match :: Equiv r c -> [c] -> Bool Source #

Derivate c (r c) => Derivate c (Equiv r c) Source # 

Methods

nullable :: Equiv r c -> Bool Source #

derivate :: c -> Equiv r c -> Equiv r c Source #

Kleene c (r c) => Kleene c (Equiv r c) Source # 

Methods

empty :: Equiv r c Source #

eps :: Equiv r c Source #

char :: c -> Equiv r c Source #

appends :: [Equiv r c] -> Equiv r c Source #

unions :: [Equiv r c] -> Equiv r c Source #

star :: Equiv r c -> Equiv r c Source #

Equivalent c (r c) => Eq (Equiv r c) Source # 

Methods

(==) :: Equiv r c -> Equiv r c -> Bool #

(/=) :: Equiv r c -> Equiv r c -> Bool #

Show (r c) => Show (Equiv r c) Source # 

Methods

showsPrec :: Int -> Equiv r c -> ShowS #

show :: Equiv r c -> String #

showList :: [Equiv r c] -> ShowS #

Semigroup (r c) => Semigroup (Equiv r c) Source # 

Methods

(<>) :: Equiv r c -> Equiv r c -> Equiv r c #

sconcat :: NonEmpty (Equiv r c) -> Equiv r c #

stimes :: Integral b => b -> Equiv r c -> Equiv r c #

Monoid (r c) => Monoid (Equiv r c) Source # 

Methods

mempty :: Equiv r c #

mappend :: Equiv r c -> Equiv r c -> Equiv r c #

mconcat :: [Equiv r c] -> Equiv r c #

JoinSemiLattice (r c) => JoinSemiLattice (Equiv r c) Source # 

Methods

(\/) :: Equiv r c -> Equiv r c -> Equiv r c #

join :: Equiv r c -> Equiv r c -> Equiv r c #

BoundedJoinSemiLattice (r c) => BoundedJoinSemiLattice (Equiv r c) Source # 

Methods

bottom :: Equiv r c #

(JoinSemiLattice (r c), Equivalent c (r c)) => PartialOrd (Equiv r c) Source #

\(a \preceq b := a \lor b = b \)

Methods

leq :: Equiv r c -> Equiv r c -> Bool #

comparable :: Equiv r c -> Equiv r c -> Bool #

Pretty (r c) => Pretty (Equiv r c) Source # 

Methods

pretty :: Equiv r c -> String Source #

prettyS :: Equiv r c -> ShowS Source #

Deterministic finite automaton

data DFA c Source #

Deterministic finite automaton.

A deterministic finite automaton (DFA) over an alphabet \(\Sigma\) (type variable c) is 4-tuple \(Q\), \(q_0\) , \(F\), \(\delta\), where

  • \(Q\) is a finite set of states (subset of Int),
  • \(q_0 \in Q\) is the distinguised start state (0),
  • \(F \subset Q\) is a set of final (or accepting) states (dfaAcceptable), and
  • \(\delta : Q \times \Sigma \to Q\) is a function called the state transition function (dfaTransition).

Constructors

DFA 

Fields

Instances

Complement c (DFA c) Source #

Complement DFA.

Complement of DFA is way easier than of RE: complement accept states.

>>> let dfa = complement $ fromRE $ RE.star "abc"
>>> putPretty dfa
0 -> \x -> if
    | x <= '`'  -> 3
    | x <= 'a'  -> 2
    | otherwise -> 3
1+ -> \x -> if
    | x <= 'b'  -> 3
    | x <= 'c'  -> 0
    | otherwise -> 3
2+ -> \x -> if
    | x <= 'a'  -> 3
    | x <= 'b'  -> 1
    | otherwise -> 3
3+ -> \_ -> 3 -- black hole
>>> map (match dfa) ["", "abc", "abcabc", "aa","abca", 'a' : 'a' : undefined]
[False,False,False,True,True,True]

Methods

complement :: DFA c -> DFA c Source #

Ord c => Match c (DFA c) Source #

Run DFA on the input.

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 RE match.

>>> let dfa = fromRE $ RE.star "abc"
>>> map (match dfa) ["", "abc", "abcabc", "aa", 'a' : 'a' : undefined]
[True,True,True,False,False]

Holds:

match (fromRE re) xs == match re xs
all (match (fromRE r)) $ take 10 $ RE.generate (curry QC.choose) 42 (r :: RE.RE Char)

Methods

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

Show c => Show (DFA c) Source # 

Methods

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

show :: DFA c -> String #

showList :: [DFA c] -> ShowS #

Show c => Pretty (DFA c) Source # 

Methods

pretty :: DFA c -> String Source #

prettyS :: DFA c -> ShowS Source #

fromTM :: forall k c. (Ord k, Ord c, TransitionMap c k) => k -> DFA c Source #

Create from TransitionMap.

See fromRE for a specific example.

fromTMEquiv :: forall k c. (Ord k, Ord c, TransitionMap c k, Equivalent c k) => k -> DFA c Source #

Create from TransitonMap minimising states with Equivalent.

See fromERE for an example.

toKleene :: forall k c. (Ord c, Enum c, Bounded c, FiniteKleene c k) => DFA c -> k Source #

Convert to any Kleene.

See toRE for a specific example.

Classes

Most operations are defined in following type-classes.

See Kleene.RE module for a specific version with examples.

class (BoundedJoinSemiLattice k, Semigroup k, Monoid k) => Kleene c k | k -> c where Source #

Minimal complete definition

char, star

Methods

empty :: k Source #

Empty regex. Doesn't accept anything.

eps :: k Source #

Empty string. Note: different than empty

char :: c -> k Source #

Single character

appends :: [k] -> k Source #

Concatenation.

unions :: [k] -> k Source #

Union.

star :: k -> k Source #

Kleene star

Instances

(Ord c, Enum c, Bounded c) => Kleene c (ERE c) Source # 

Methods

empty :: ERE c Source #

eps :: ERE c Source #

char :: c -> ERE c Source #

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

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

star :: ERE c -> ERE c Source #

Kleene c (M c) Source # 

Methods

empty :: M c Source #

eps :: M c Source #

char :: c -> M c Source #

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

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

star :: M c -> M c Source #

(Ord c, Enum c, Bounded c) => Kleene c (RE c) Source # 

Methods

empty :: RE c Source #

eps :: RE c Source #

char :: c -> RE c Source #

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

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

star :: RE c -> RE c Source #

Kleene c (r c) => Kleene c (Equiv r c) Source # 

Methods

empty :: Equiv r c Source #

eps :: Equiv r c Source #

char :: c -> Equiv r c Source #

appends :: [Equiv r c] -> Equiv r c Source #

unions :: [Equiv r c] -> Equiv r c Source #

star :: Equiv r c -> Equiv r c Source #

class Derivate c k | k -> c where Source #

Minimal complete definition

nullable, derivate

Methods

nullable :: k -> Bool Source #

Does language contain an empty string?

derivate :: c -> k -> k Source #

Derivative of a language.

Instances

(Ord c, Enum c) => Derivate c (ERE c) Source # 

Methods

nullable :: ERE c -> Bool Source #

derivate :: c -> ERE c -> ERE c Source #

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

Methods

nullable :: M c -> Bool Source #

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

(Ord c, Enum c, Bounded c) => Derivate c (RE c) Source # 

Methods

nullable :: RE c -> Bool Source #

derivate :: c -> RE c -> RE c Source #

Derivate c (r c) => Derivate c (Equiv r c) Source # 

Methods

nullable :: Equiv r c -> Bool Source #

derivate :: c -> Equiv r c -> Equiv r c Source #

class Match c k | k -> c where Source #

An f can be used to match on the input.

Minimal complete definition

match

Methods

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

Instances

(Ord c, Enum c) => Match c (ERE c) Source # 

Methods

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

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

Methods

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

(Ord c, Enum c, Bounded c) => Match c (RE c) Source # 

Methods

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

Ord c => Match c (DFA c) Source #

Run DFA on the input.

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 RE match.

>>> let dfa = fromRE $ RE.star "abc"
>>> map (match dfa) ["", "abc", "abcabc", "aa", 'a' : 'a' : undefined]
[True,True,True,False,False]

Holds:

match (fromRE re) xs == match re xs
all (match (fromRE r)) $ take 10 $ RE.generate (curry QC.choose) 42 (r :: RE.RE Char)

Methods

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

Match c (r c) => Match c (Equiv r c) Source # 

Methods

match :: Equiv r c -> [c] -> Bool Source #

class Derivate c k => TransitionMap c k | k -> c where Source #

Transition map.

Minimal complete definition

transitionMap

Methods

transitionMap :: k -> Map k (SF c k) Source #

Instances

(Ord c, Enum c, Bounded c) => TransitionMap c (ERE c) Source # 

Methods

transitionMap :: ERE c -> Map (ERE c) (SF c (ERE c)) Source #

(Ord c, Enum c, Bounded c) => TransitionMap c (RE c) Source # 

Methods

transitionMap :: RE c -> Map (RE c) (SF c (RE c)) Source #

class Complement c k | k -> c where Source #

Complement of the language.

Law:

matches (complement f) xs = not (matches f) xs

Minimal complete definition

complement

Methods

complement :: k -> k Source #

Instances

Complement c (ERE c) Source # 

Methods

complement :: ERE c -> ERE c Source #

Complement c (DFA c) Source #

Complement DFA.

Complement of DFA is way easier than of RE: complement accept states.

>>> let dfa = complement $ fromRE $ RE.star "abc"
>>> putPretty dfa
0 -> \x -> if
    | x <= '`'  -> 3
    | x <= 'a'  -> 2
    | otherwise -> 3
1+ -> \x -> if
    | x <= 'b'  -> 3
    | x <= 'c'  -> 0
    | otherwise -> 3
2+ -> \x -> if
    | x <= 'a'  -> 3
    | x <= 'b'  -> 1
    | otherwise -> 3
3+ -> \_ -> 3 -- black hole
>>> map (match dfa) ["", "abc", "abcabc", "aa","abca", 'a' : 'a' : undefined]
[False,False,False,True,True,True]

Methods

complement :: DFA c -> DFA c Source #

Complement c (r c) => Complement c (Equiv r c) Source # 

Methods

complement :: Equiv r c -> Equiv r c Source #

Functor

Only the type is exported so it can be referred to.

See Kleene.Functor for operations.

data K c a Source #

Applicative Functor regular expression.

Instances

Functor (K c) Source # 

Methods

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

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

Applicative (K c) Source # 

Methods

pure :: a -> K c a #

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

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

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

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

Alternative (K c) Source # 

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

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

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)*$

Methods

pretty :: K c a -> String Source #

prettyS :: K c a -> ShowS Source #