Safe Haskell | None |
---|---|
Language | Haskell2010 |
This Text.Regex.TDFA.Pattern module provides the Pattern
data
type and its subtypes. This Pattern
type is used to represent
the parsed form of a regular expression.
Synopsis
- data Pattern
- = PEmpty
- | PGroup (Maybe GroupIndex) Pattern
- | POr [Pattern]
- | PConcat [Pattern]
- | PQuest Pattern
- | PPlus Pattern
- | PStar Bool Pattern
- | PBound Int (Maybe Int) Pattern
- | PCarat { }
- | PDollar { }
- | PDot { }
- | PAny { }
- | PAnyNot { }
- | PEscape {
- getDoPa :: DoPa
- getPatternChar :: Char
- | PChar {
- getDoPa :: DoPa
- getPatternChar :: Char
- | PNonCapture Pattern
- | PNonEmpty Pattern
- data PatternSet = PatternSet (Maybe (Set Char)) (Maybe (Set PatternSetCharacterClass)) (Maybe (Set PatternSetCollatingElement)) (Maybe (Set PatternSetEquivalenceClass))
- newtype PatternSetCharacterClass = PatternSetCharacterClass {}
- newtype PatternSetCollatingElement = PatternSetCollatingElement {}
- newtype PatternSetEquivalenceClass = PatternSetEquivalenceClass {}
- type GroupIndex = Int
- newtype DoPa = DoPa {}
- decodeCharacterClass :: PatternSetCharacterClass -> String
- decodePatternSet :: PatternSet -> Set Char
- showPattern :: Pattern -> String
- starTrans :: Pattern -> Pattern
- starTrans' :: Pattern -> Pattern
- simplify' :: Pattern -> Pattern
- dfsPattern :: (Pattern -> Pattern) -> Pattern -> Pattern
Documentation
Pattern
is the type returned by the regular expression parser parseRegex
.
This is consumed by the Text.Regex.TDFA.CorePattern module and the tender leaves
are nibbled by the Text.Regex.TDFA.TNFA module.
The DoPa
field is the index of the component in the regex string r
.
PEmpty |
|
PGroup (Maybe GroupIndex) Pattern | Group |
POr [Pattern] | Alternative |
PConcat [Pattern] | Sequence |
PQuest Pattern | Zero or one repetitions |
PPlus Pattern | One or more repetitions |
PStar Bool Pattern | Zero or more repetitions |
PBound Int (Maybe Int) Pattern | Given number or repetitions |
PCarat |
|
PDollar |
|
PDot |
|
PAny | Bracket expression |
| |
PAnyNot | Inverted bracket expression |
| |
PEscape | Backslashed character |
| |
PChar | Single character, matches given character. |
| |
PNonCapture Pattern | Tag for internal use, introduced by |
PNonEmpty Pattern | Tag for internal use, introduced by |
data PatternSet Source #
Content of a bracket expression [...]
organized into
characters,
POSIX character classes (e.g. [[:alnum:]]
),
collating elements (e.g. [.ch.]
, unused), and
equivalence classes (e.g. [=a=]
, treated as characters).
PatternSet (Maybe (Set Char)) (Maybe (Set PatternSetCharacterClass)) (Maybe (Set PatternSetCollatingElement)) (Maybe (Set PatternSetEquivalenceClass)) |
Instances
Eq PatternSet Source # | |
Defined in Text.Regex.TDFA.Pattern (==) :: PatternSet -> PatternSet -> Bool Source # (/=) :: PatternSet -> PatternSet -> Bool Source # | |
Show PatternSet Source # | Hand-rolled implementation, giving textual rather than Haskell representation. |
Defined in Text.Regex.TDFA.Pattern |
newtype PatternSetCharacterClass Source #
Content of [: :]
, e.g. "alnum"
for [:alnum:]
.
Instances
Eq PatternSetCharacterClass Source # | |
Defined in Text.Regex.TDFA.Pattern | |
Ord PatternSetCharacterClass Source # | |
Defined in Text.Regex.TDFA.Pattern compare :: PatternSetCharacterClass -> PatternSetCharacterClass -> Ordering Source # (<) :: PatternSetCharacterClass -> PatternSetCharacterClass -> Bool Source # (<=) :: PatternSetCharacterClass -> PatternSetCharacterClass -> Bool Source # (>) :: PatternSetCharacterClass -> PatternSetCharacterClass -> Bool Source # (>=) :: PatternSetCharacterClass -> PatternSetCharacterClass -> Bool Source # max :: PatternSetCharacterClass -> PatternSetCharacterClass -> PatternSetCharacterClass Source # min :: PatternSetCharacterClass -> PatternSetCharacterClass -> PatternSetCharacterClass Source # | |
Show PatternSetCharacterClass Source # | Hand-rolled implementation, giving textual rather than Haskell representation. |
Defined in Text.Regex.TDFA.Pattern |
newtype PatternSetCollatingElement Source #
Content of [. .]
, e.g. "ch"
for [.ch.]
.
Instances
Eq PatternSetCollatingElement Source # | |
Defined in Text.Regex.TDFA.Pattern | |
Ord PatternSetCollatingElement Source # | |
Defined in Text.Regex.TDFA.Pattern compare :: PatternSetCollatingElement -> PatternSetCollatingElement -> Ordering Source # (<) :: PatternSetCollatingElement -> PatternSetCollatingElement -> Bool Source # (<=) :: PatternSetCollatingElement -> PatternSetCollatingElement -> Bool Source # (>) :: PatternSetCollatingElement -> PatternSetCollatingElement -> Bool Source # (>=) :: PatternSetCollatingElement -> PatternSetCollatingElement -> Bool Source # max :: PatternSetCollatingElement -> PatternSetCollatingElement -> PatternSetCollatingElement Source # min :: PatternSetCollatingElement -> PatternSetCollatingElement -> PatternSetCollatingElement Source # | |
Show PatternSetCollatingElement Source # | Hand-rolled implementation, giving textual rather than Haskell representation. |
Defined in Text.Regex.TDFA.Pattern |
newtype PatternSetEquivalenceClass Source #
Content of [= =]
, e.g. "a"
for [=a=]
.
Instances
Eq PatternSetEquivalenceClass Source # | |
Defined in Text.Regex.TDFA.Pattern | |
Ord PatternSetEquivalenceClass Source # | |
Defined in Text.Regex.TDFA.Pattern compare :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> Ordering Source # (<) :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> Bool Source # (<=) :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> Bool Source # (>) :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> Bool Source # (>=) :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> Bool Source # max :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> PatternSetEquivalenceClass Source # min :: PatternSetEquivalenceClass -> PatternSetEquivalenceClass -> PatternSetEquivalenceClass Source # | |
Show PatternSetEquivalenceClass Source # | Hand-rolled implementation, giving textual rather than Haskell representation. |
Defined in Text.Regex.TDFA.Pattern |
type GroupIndex = Int Source #
GroupIndex
is for indexing submatches from capturing parenthesized groups (PGroup
or Group
).
Used to track elements of the pattern that accept characters or are anchors.
Instances
decodeCharacterClass :: PatternSetCharacterClass -> String Source #
This returns the strictly ascending list of characters
represented by [: :]
POSIX character classes.
Unrecognized class names return an empty string.
Since: 1.3.2
decodePatternSet :: PatternSet -> Set Char Source #
decodePatternSet
cannot handle collating element and treats
equivalence classes as just their definition and nothing more.
Since: 1.3.2
showPattern :: Pattern -> String Source #
Internal use
starTrans :: Pattern -> Pattern Source #
Do the transformation and simplification in a single traversal.
This removes the PPlus
, PQuest
, and PBound
values, changing to POr
and PEmpty
and PStar
. For some PBound
values it adds
PNonEmpty
and PNonCapture
semantic marker. It also simplifies to
flatten out nested POr
and PConcat
instances and eliminate some
unneeded PEmpty
values.
Internal use, operations to support debugging under ghci
starTrans' :: Pattern -> Pattern Source #