regex-tdfa-1.1.1: Replaces/Enhances Text.RegexContentsIndex
Text.Regex.TDFA.Pattern
Contents
Internal use
Internal use, Operations to support debugging under ghci
Description
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 {
getDoPa :: DoPa
}
| PDollar {
getDoPa :: DoPa
}
| PDot {
getDoPa :: DoPa
}
| PAny {
getDoPa :: DoPa
getPatternSet :: PatternSet
}
| PAnyNot {
getDoPa :: DoPa
getPatternSet :: PatternSet
}
| 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 {
unSCC :: String
}
newtype PatternSetCollatingElement = PatternSetCollatingElement {
unSCE :: String
}
newtype PatternSetEquivalenceClass = PatternSetEquivalenceClass {
unSEC :: String
}
type GroupIndex = Int
newtype DoPa = DoPa {
dopaIndex :: Int
}
showPattern :: Pattern -> String
starTrans :: Pattern -> Pattern
starTrans' :: Pattern -> Pattern
simplify' :: Pattern -> Pattern
dfsPattern :: (Pattern -> Pattern) -> Pattern -> Pattern
Documentation
data Pattern
Pattern is the type returned by the regular expression parser. This is consumed by the CorePattern module and the tender leaves are nibbled by the TNFA module.
Constructors
PEmpty
PGroup (Maybe GroupIndex) Pattern
POr [Pattern]
PConcat [Pattern]
PQuest Pattern
PPlus Pattern
PStar Bool Pattern
PBound Int (Maybe Int) Pattern
PCarat
getDoPa :: DoPa
PDollar
getDoPa :: DoPa
PDot
getDoPa :: DoPa
PAny
getDoPa :: DoPa
getPatternSet :: PatternSet
PAnyNot
getDoPa :: DoPa
getPatternSet :: PatternSet
PEscape
getDoPa :: DoPa
getPatternChar :: Char
PChar
getDoPa :: DoPa
getPatternChar :: Char
PNonCapture Pattern
PNonEmpty Pattern
show/hide Instances
data PatternSet
Constructors
PatternSet (Maybe (Set Char)) (Maybe (Set PatternSetCharacterClass)) (Maybe (Set PatternSetCollatingElement)) (Maybe (Set PatternSetEquivalenceClass))
show/hide Instances
newtype PatternSetCharacterClass
Constructors
PatternSetCharacterClass
unSCC :: String
show/hide Instances
newtype PatternSetCollatingElement
Constructors
PatternSetCollatingElement
unSCE :: String
show/hide Instances
newtype PatternSetEquivalenceClass
Constructors
PatternSetEquivalenceClass
unSEC :: String
show/hide Instances
type GroupIndex = Int
GroupIndex is for indexing submatches from capturing parenthesized groups (PGroup/Group)
newtype DoPa
Used to track elements of the pattern that accept characters or are anchors
Constructors
DoPa
dopaIndex :: Int
show/hide Instances
showPattern :: Pattern -> String
I have not been checking, but this should have the property that parsing the resulting string should result in an identical Pattern. This is not true if starTrans has created PNonCapture and PNonEmpty values or a (PStar False). The contents of a [ ] grouping are always shown in a sorted canonical order.
Internal use
starTrans :: Pattern -> Pattern
Do the transformation and simplification in a single traversal. This removes the PPlus, PQuest, and PBound values, changing to POr and PEmpty and PStar True/False. 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 uneeded PEmpty values.
Internal use, Operations to support debugging under ghci
starTrans' :: Pattern -> Pattern
simplify' :: Pattern -> Pattern
Function to transform a pattern into an equivalent, but less redundant form. Nested POr and PConcat are flattened. PEmpty is propagated.
dfsPattern
:: Pattern -> PatternThe transformation function
-> PatternThe Pattern to transform
-> PatternThe transformed Pattern
Apply a Pattern transfomation function depth first
Produced by Haddock version 2.3.0