regex-tdfa-1.3.2: Pure Haskell Tagged DFA Backend for "Text.Regex" (regex-base)
Safe HaskellNone
LanguageHaskell2010

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

Documentation

data Pattern Source #

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.

Constructors

PEmpty

(), matches the empty string.

PGroup (Maybe GroupIndex) Pattern

Group (r). Nothing indicates non-matching PGroup (never produced by parser parseRegex).

POr [Pattern]

Alternative r|s (flattened by starTrans).

PConcat [Pattern]

Sequence rs (flattened by starTrans).

PQuest Pattern

Zero or one repetitions r? (eliminated by starTrans).

PPlus Pattern

One or more repetitions r+ (eliminated by starTrans).

PStar Bool Pattern

Zero or more repetitions r*. True (default) means may accept the empty string on its first iteration.

PBound Int (Maybe Int) Pattern

Given number or repetitions r{n} or r{n,m} (eliminated by starTrans).

PCarat

^ matches beginning of input.

Fields

PDollar

$ matches end of input.

Fields

PDot

. matches any character.

Fields

PAny

Bracket expression [...].

PAnyNot

Inverted bracket expression [^...].

PEscape

Backslashed character c, may have special meaning.

PChar

Single character, matches given character.

PNonCapture Pattern

Tag for internal use, introduced by starTrans.

PNonEmpty Pattern

Tag for internal use, introduced by starTrans.

Instances

Instances details
Eq Pattern Source # 
Instance details

Defined in Text.Regex.TDFA.Pattern

Methods

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

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

Show Pattern Source # 
Instance details

Defined in Text.Regex.TDFA.Pattern

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).

Instances

Instances details
Eq PatternSet Source # 
Instance details

Defined in Text.Regex.TDFA.Pattern

Show PatternSet Source #

Hand-rolled implementation, giving textual rather than Haskell representation.

Instance details

Defined in Text.Regex.TDFA.Pattern

type GroupIndex = Int Source #

GroupIndex is for indexing submatches from capturing parenthesized groups (PGroup or Group).

newtype DoPa Source #

Used to track elements of the pattern that accept characters or are anchors.

Constructors

DoPa 

Fields

Instances

Instances details
Enum DoPa Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

succ :: DoPa -> DoPa #

pred :: DoPa -> DoPa #

toEnum :: Int -> DoPa #

fromEnum :: DoPa -> Int #

enumFrom :: DoPa -> [DoPa] #

enumFromThen :: DoPa -> DoPa -> [DoPa] #

enumFromTo :: DoPa -> DoPa -> [DoPa] #

enumFromThenTo :: DoPa -> DoPa -> DoPa -> [DoPa] #

Eq DoPa Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

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

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

Ord DoPa Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

compare :: DoPa -> DoPa -> Ordering #

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

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

(>) :: DoPa -> DoPa -> Bool #

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

max :: DoPa -> DoPa -> DoPa #

min :: DoPa -> DoPa -> DoPa #

Show DoPa Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> DoPa -> ShowS #

show :: DoPa -> String #

showList :: [DoPa] -> ShowS #

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

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

simplify' :: Pattern -> Pattern Source #

Function to transform a pattern into an equivalent, but less redundant form. Nested POr and PConcat are flattened. PEmpty is propagated.

dfsPattern Source #

Arguments

:: (Pattern -> Pattern)

The transformation function.

-> Pattern

The Pattern to transform.

-> Pattern

The transformed Pattern.

Apply a Pattern transformation function depth first.