| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.Regex.TDFA.Pattern
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 { }
- | 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 {}
- 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. 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 | |
| PDollar | |
| PDot | |
| PAny | |
| Fields 
 | |
| PAnyNot | |
| Fields 
 | |
| PEscape | |
| Fields 
 | |
| PChar | |
| Fields 
 | |
| PNonCapture Pattern | |
| PNonEmpty Pattern | |
Instances
data PatternSet Source #
Constructors
| PatternSet (Maybe (Set Char)) (Maybe (Set PatternSetCharacterClass)) (Maybe (Set PatternSetCollatingElement)) (Maybe (Set PatternSetEquivalenceClass)) | 
Instances
| Eq PatternSet Source # | |
| Defined in Text.Regex.TDFA.Pattern | |
| Show PatternSet Source # | |
| Defined in Text.Regex.TDFA.Pattern Methods showsPrec :: Int -> PatternSet -> ShowS # show :: PatternSet -> String # showList :: [PatternSet] -> ShowS # | |
newtype PatternSetCharacterClass Source #
Constructors
| PatternSetCharacterClass | |
Instances
newtype PatternSetCollatingElement Source #
Constructors
| PatternSetCollatingElement | |
Instances
newtype PatternSetEquivalenceClass Source #
Constructors
| PatternSetEquivalenceClass | |
Instances
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.
showPattern :: Pattern -> String Source #
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 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 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 unneeded PEmpty values.
Internal use, Operations to support debugging under ghci
starTrans' :: Pattern -> Pattern Source #