sasha-0.1: A staged lexer generator
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sasha.Internal.ERE

Synopsis

Documentation

data ERE Source #

Extended regular expression

Constructors

EREAppend [ERE]

Concatenation

EREUnion Word8Set (Set ERE)

Union

EREStar ERE

Kleene star

ERENot ERE

Complement

Instances

Instances details
Arbitrary ERE Source #

Uses smart constructors.

Instance details

Defined in Sasha.Internal.ERE

Methods

arbitrary :: Gen ERE #

shrink :: ERE -> [ERE] #

IsString ERE Source #

Uses utf8string.

Instance details

Defined in Sasha.Internal.ERE

Methods

fromString :: String -> ERE #

Monoid ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

mempty :: ERE #

mappend :: ERE -> ERE -> ERE #

mconcat :: [ERE] -> ERE #

Semigroup ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

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

sconcat :: NonEmpty ERE -> ERE #

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

Show ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

showsPrec :: Int -> ERE -> ShowS #

show :: ERE -> String #

showList :: [ERE] -> ShowS #

Eq ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

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

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

Ord ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

compare :: ERE -> ERE -> Ordering #

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

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

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

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

max :: ERE -> ERE -> ERE #

min :: ERE -> ERE -> ERE #

BoundedJoinSemiLattice ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

bottom :: ERE #

BoundedMeetSemiLattice ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

top :: ERE #

Lattice ERE Source # 
Instance details

Defined in Sasha.Internal.ERE

Methods

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

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

Construction

Binary operators are

  • <> for append
  • \/ for union
  • /\ for intersection

empty :: ERE Source #

Empty regex. Doesn't accept anything.

match empty s === False

eps :: ERE Source #

Empty string. Note: different than empty.

match eps s === null s

char :: Word8 -> ERE Source #

Character.

charRange :: Word8 -> Word8 -> ERE Source #

Character range.

utf8Char :: Char -> ERE Source #

UTF8 character, i.e. may match multiple bytes.

anyChar :: ERE Source #

Any character.

appends :: [ERE] -> ERE Source #

Concatenate regular expressions.

r <> empty === empty
empty <>  r === empty
( r <> s) <> t === r <> (s <> t)
r <> eps === r
eps <>  r === r

unions :: [ERE] -> ERE Source #

Union of regular expressions.

r \/ r === r
r \/ s === s \/ r
( r \/ s) \/ t === r \/ (s \/ t)
empty \/  r === r
r \/ empty === r
everything \/  r === everything
r \/ everything === everything

intersections :: [ERE] -> ERE Source #

Intersection of regular expressions.

r /\ r === r
r /\ s === s /\ r
( r /\ s) /\ t === r /\ (s /\ t)
empty /\  r === empty
r /\ empty === empty
everything /\  r === r
r /\ everything === r

star :: ERE -> ERE Source #

Kleene star.

star (star r) === star ( r)
star eps     ===  eps
star empty   ===  eps
star anyChar ===  everything
star (r \/ eps) === star r
star (char c \/ eps) === star (char c)
star (empty \/ eps) === eps

plus :: ERE -> ERE Source #

Kleene plus

plus r = r <> star r

string :: [Word8] -> ERE Source #

Literal string.

utf8String :: String -> ERE Source #

UTF8 string

complement :: ERE -> ERE Source #

Complement.

complement (complement r) ===  r

everything :: ERE Source #

Everything.

match everything s === True

Equivalence

Derivative

nullable :: ERE -> 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
>>> nullable (complement eps)
False

derivative :: Word8 -> ERE -> ERE 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}\).

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

Other

isEmpty :: ERE -> Bool Source #

Whether ERE is (structurally) equal to empty.

isEverything :: ERE -> Bool Source #

Whether ERE is (structurally) equal to everything.