regex-tdfa-0.97.3: Accurate POSIX extended regular expression library

Text.Regex.TDFA.Common

Description

Common provides simple functions to the backend. It defines most of the data types. All modules should call error via the common_error function below.

Synopsis

Documentation

look :: Int -> IntMap a -> aSource

on :: (t1 -> t1 -> t2) -> (t -> t1) -> t -> t -> t2Source

norep :: Eq a => [a] -> [a]Source

after sort or sortBy the use of nubnubBy can be replaced by norepnorepBy

norepBy :: (a -> a -> Bool) -> [a] -> [a]Source

after sort or sortBy the use of nubnubBy can be replaced by norepnorepBy

mapFst :: Functor f => (t -> t2) -> f (t, t1) -> f (t2, t1)Source

mapSnd :: Functor f => (t1 -> t2) -> f (t, t1) -> f (t, t2)Source

fst3 :: (a, b, c) -> aSource

snd3 :: (a, b, c) -> bSource

thd3 :: (a, b, c) -> cSource

newtype DoPa Source

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

Constructors

DoPa 

Fields

dopaIndex :: Int
 

Instances

data CompOption Source

Control whether the pattern is multiline or case-sensitive like Text.Regex and whether to capture the subgroups (1, 2, etc).

Constructors

CompOption 

Fields

caseSensitive :: Bool

True by default

multiline :: Bool

True by default, implies . and [^a] will not match '\n'

rightAssoc :: Bool

False (and therefore left associative) by default

lastStarGreedy :: Bool

False by default. This is POSIX correct by takes space and is slower. Setting this to true will improve performance, and should be done if you plan to set the captureGroups execoption to False.

data ExecOption Source

Constructors

ExecOption 

Fields

captureGroups :: Bool

True by default. Set to False to improve speed (and space).

testMatch :: Bool

False by default. Set to True to quickly return shortest match (w/o groups). [ UNUSED ]

type TagSource

Arguments

 = Int

identity of Position tag to set during a transition | Internal use to indicate type of tag and preference for larger or smaller Positions

Used by implementation to name certain Postions during matching

data OP Source

Constructors

Maximize 
Minimize 
Orbit 

Instances

type IndexSource

Arguments

 = Int

Internal NFA node identity number

type SetIndexSource

Arguments

 = IntSet

Internal DFA identity is this Set of NFA Index

type PositionSource

Arguments

 = Int

Index into the text being searched

type GroupIndex = IntSource

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

data GroupInfo Source

GroupInfo collects the parent and tag information for an instance of a group

Instances

data QNFA Source

Internal NFA node type

Constructors

QNFA 

Fields

q_id :: Index
 
q_qt :: QT
 

Instances

data QT Source

Internal to QNFA type.

Constructors

Simple 

Fields

qt_win :: WinTags

empty transitions to the virtual winning state

qt_trans :: CharMap QTrans

all ways to leave this QNFA to other or the same QNFA

qt_other :: QTrans

default ways to leave this QNFA to other or the same QNFA

Testing 

Fields

qt_test :: WhichTest

The test to perform

qt_dopas :: EnumSet DoPa

location(s) of the anchor(s) in the original regexp

qt_a :: QT

use qt_a if test is True, else use qt_b

qt_b :: QT

use qt_a if test is True, else use qt_b

Instances

type QTrans = IntMap [TagCommand]Source

Internal type to represent the tagged transition from one QNFA to another (or itself). The key is the Index of the destination QNFA.

data WhichTest Source

Known predicates, just Beginning of Line (^) and End of Line ($).

Constructors

Test_BOL 
Test_EOL 

data TagTask Source

The things that can be done with a Tag. TagTask and ResetGroupStopTask are for tags with Maximize or Minimize OP values. ResetOrbitTask and EnterOrbitTask and LeaveOrbitTask are for tags with Orbit OP value.

Instances

type TagTasks = [(Tag, TagTask)]Source

Ordered list of tags and their associated Task

data TagUpdate Source

When attached to a QTrans the TagTask can be done before or after accepting the character.

type TagList = [(Tag, TagUpdate)]Source

Ordered list of tags and their associated update operation.

type TagCommand = (DoPa, TagList)Source

A TagList and the location of the item in the original pattern that is being accepted.

type WinTags = TagListSource

Ordered list of tags and their associated update operation to perform on an empty transition to the virtual winning state.

data DFA Source

Internal DFA node, identified by the Set of indices of the QNFA nodes it represents.

Constructors

DFA 

Fields

d_id :: SetIndex
 
d_dt :: DT
 

Instances

data DT Source

Internal to the DFA node

Constructors

Simple' 

Fields

dt_win :: IntMap Instructions

Actions to perform to win

dt_trans :: CharMap (DFA, DTrans)

Transition to accept Char

dt_other :: Maybe (DFA, DTrans)

Optional default accepting transition

Testing' 

Fields

dt_test :: WhichTest

The test to perform

dt_dopas :: EnumSet DoPa

location(s) of the anchor(s) in the original regexp

dt_a :: DT

use dt_a if test is True else use dt_b

dt_b :: DT

use dt_a if test is True else use dt_b

Instances

type DTrans = IntMap (IntMap (DoPa, Instructions))Source

Internal type to repesent the commands for the tagged transition. The outer IntMap is for the destination Index and the inner IntMap is for the Source Index. This is convenient since all runtime data going to the same destination must be compared to find the best.

type DTrans' = [(Index, [(Index, (DoPa, ([(Tag, (Position, Bool))], [String])))])]Source

Internal convenience type for the text display code

data Orbits Source

Positions for which a * was re-started while looping. Need to append locations but compare starting with front, so use Seq as a Queue.

Constructors

Orbits 

Fields

inOrbit :: !Bool
 
getOrbits :: !(Seq Position)
 

Instances

data Instructions Source

Constructors

Instructions 

Fields

newPos :: ![(Tag, Bool)]
 
newFlags :: ![(Tag, Bool)]
 
newOrbits :: !(Maybe (Position -> OrbitTransformer))
 

Instances