regex-tdfa-1.3.2.1: Pure Haskell Tagged DFA Backend for "Text.Regex" (regex-base)
Safe HaskellSafe-Inferred
LanguageHaskell2010

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 -> a Source #

common_error :: String -> String -> a Source #

on :: (t1 -> t1 -> t2) -> (t -> t1) -> t -> t -> t2 Source #

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

After sort or sortBy the use of nub or nubBy can be replaced by norep or norepBy.

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

After sort or sortBy the use of nub or nubBy can be replaced by norep or norepBy.

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) -> a Source #

snd3 :: (a, b, c) -> b Source #

thd3 :: (a, b, c) -> c Source #

flipOrder :: Ordering -> Ordering Source #

noWin :: WinTags -> Bool Source #

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]

Show DoPa Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> DoPa -> ShowS

show :: DoPa -> String

showList :: [DoPa] -> ShowS

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

data CompOption Source #

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

Constructors

CompOption 

Fields

  • caseSensitive :: Bool

    True in blankCompOpt and defaultCompOpt.

  • multiline :: Bool

    False in blankCompOpt, True in defaultCompOpt. Compile for newline-sensitive matching.

    From regexp man page: "By default, newline is a completely ordinary character with no special meaning in either REs or strings. With this flag, inverted bracket expressions [^ and . never match newline, a ^ anchor matches the null string after any newline in the string in addition to its normal function, and the $ anchor matches the null string before any newline in the string in addition to its normal function."

  • rightAssoc :: Bool

    True (and therefore right associative) in blankCompOpt and defaultCompOpt.

  • newSyntax :: Bool

    False in blankCompOpt, True in defaultCompOpt. Enables the extended non-POSIX syntax described in Text.Regex.TDFA haddock documentation.

  • lastStarGreedy :: Bool

    False by default. This is POSIX correct but it 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.

Instances

Instances details
Read CompOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

readsPrec :: Int -> ReadS CompOption

readList :: ReadS [CompOption]

readPrec :: ReadPrec CompOption

readListPrec :: ReadPrec [CompOption]

Show CompOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> CompOption -> ShowS

show :: CompOption -> String

showList :: [CompOption] -> ShowS

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexMaker Regex CompOption ExecOption ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString

Methods

makeRegex :: ByteString -> Regex

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex

makeRegexM :: MonadFail m => ByteString -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex

RegexMaker Regex CompOption ExecOption ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex

makeRegexM :: MonadFail m => ByteString -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex

RegexMaker Regex CompOption ExecOption Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text

Methods

makeRegex :: Text -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Text -> Regex

makeRegexM :: MonadFail m => Text -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Text -> m Regex

RegexMaker Regex CompOption ExecOption Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text.Lazy

Methods

makeRegex :: Text -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Text -> Regex

makeRegexM :: MonadFail m => Text -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Text -> m Regex

RegexMaker Regex CompOption ExecOption String 
Instance details

Defined in Text.Regex.TDFA.String

Methods

makeRegex :: String -> Regex

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex

makeRegexM :: MonadFail m => String -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex

RegexMaker Regex CompOption ExecOption (Seq Char) 
Instance details

Defined in Text.Regex.TDFA.Sequence

Methods

makeRegex :: Seq Char -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex

makeRegexM :: MonadFail m => Seq Char -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex

data ExecOption Source #

Constructors

ExecOption 

Fields

  • captureGroups :: Bool

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

Instances

Instances details
Read ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

readsPrec :: Int -> ReadS ExecOption

readList :: ReadS [ExecOption]

readPrec :: ReadPrec ExecOption

readListPrec :: ReadPrec [ExecOption]

Show ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> ExecOption -> ShowS

show :: ExecOption -> String

showList :: [ExecOption] -> ShowS

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexMaker Regex CompOption ExecOption ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString

Methods

makeRegex :: ByteString -> Regex

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex

makeRegexM :: MonadFail m => ByteString -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex

RegexMaker Regex CompOption ExecOption ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex

makeRegexM :: MonadFail m => ByteString -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex

RegexMaker Regex CompOption ExecOption Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text

Methods

makeRegex :: Text -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Text -> Regex

makeRegexM :: MonadFail m => Text -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Text -> m Regex

RegexMaker Regex CompOption ExecOption Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text.Lazy

Methods

makeRegex :: Text -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Text -> Regex

makeRegexM :: MonadFail m => Text -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Text -> m Regex

RegexMaker Regex CompOption ExecOption String 
Instance details

Defined in Text.Regex.TDFA.String

Methods

makeRegex :: String -> Regex

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex

makeRegexM :: MonadFail m => String -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex

RegexMaker Regex CompOption ExecOption (Seq Char) 
Instance details

Defined in Text.Regex.TDFA.Sequence

Methods

makeRegex :: Seq Char -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex

makeRegexM :: MonadFail m => Seq Char -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex

type Tag = Int Source #

Used by implementation to name certain Postions during matching. Identity of Position tag to set during a transition.

data OP Source #

Internal use to indicate type of tag and preference for larger or smaller Positions.

Constructors

Maximize 
Minimize 
Orbit 
Ignore 

Instances

Instances details
Show OP Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> OP -> ShowS

show :: OP -> String

showList :: [OP] -> ShowS

Eq OP Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

(==) :: OP -> OP -> Bool

(/=) :: OP -> OP -> Bool

type Index = Int Source #

Internal NFA node identity number.

type SetIndex = IntSet Source #

Internal DFA identity is this Set of NFA Index.

type Position = Int Source #

Index into the text being searched.

type GroupIndex = Int Source #

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

data GroupInfo Source #

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

Instances

Instances details
Show GroupInfo Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> GroupInfo -> ShowS

show :: GroupInfo -> String

showList :: [GroupInfo] -> ShowS

data Regex Source #

The TDFA backend specific Regex type, used by this module's RegexOptions and RegexMaker.

Constructors

Regex 

Fields

Instances

Instances details
RegexLike Regex ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString

Methods

matchOnce :: Regex -> ByteString -> Maybe MatchArray

matchAll :: Regex -> ByteString -> [MatchArray]

matchCount :: Regex -> ByteString -> Int

matchTest :: Regex -> ByteString -> Bool

matchAllText :: Regex -> ByteString -> [MatchText ByteString]

matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString)

RegexLike Regex ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

Methods

matchOnce :: Regex -> ByteString -> Maybe MatchArray

matchAll :: Regex -> ByteString -> [MatchArray]

matchCount :: Regex -> ByteString -> Int

matchTest :: Regex -> ByteString -> Bool

matchAllText :: Regex -> ByteString -> [MatchText ByteString]

matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString)

RegexLike Regex Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text

Methods

matchOnce :: Regex -> Text -> Maybe MatchArray

matchAll :: Regex -> Text -> [MatchArray]

matchCount :: Regex -> Text -> Int

matchTest :: Regex -> Text -> Bool

matchAllText :: Regex -> Text -> [MatchText Text]

matchOnceText :: Regex -> Text -> Maybe (Text, MatchText Text, Text)

RegexLike Regex Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text.Lazy

Methods

matchOnce :: Regex -> Text -> Maybe MatchArray

matchAll :: Regex -> Text -> [MatchArray]

matchCount :: Regex -> Text -> Int

matchTest :: Regex -> Text -> Bool

matchAllText :: Regex -> Text -> [MatchText Text]

matchOnceText :: Regex -> Text -> Maybe (Text, MatchText Text, Text)

RegexLike Regex String 
Instance details

Defined in Text.Regex.TDFA.String

Methods

matchOnce :: Regex -> String -> Maybe MatchArray

matchAll :: Regex -> String -> [MatchArray]

matchCount :: Regex -> String -> Int

matchTest :: Regex -> String -> Bool

matchAllText :: Regex -> String -> [MatchText String]

matchOnceText :: Regex -> String -> Maybe (String, MatchText String, String)

RegexContext Regex ByteString ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString

Methods

match :: Regex -> ByteString -> ByteString

matchM :: MonadFail m => Regex -> ByteString -> m ByteString

RegexContext Regex ByteString ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

Methods

match :: Regex -> ByteString -> ByteString

matchM :: MonadFail m => Regex -> ByteString -> m ByteString

RegexContext Regex Text Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text

Methods

match :: Regex -> Text -> Text

matchM :: MonadFail m => Regex -> Text -> m Text

RegexContext Regex Text Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text.Lazy

Methods

match :: Regex -> Text -> Text

matchM :: MonadFail m => Regex -> Text -> m Text

RegexContext Regex String String 
Instance details

Defined in Text.Regex.TDFA.String

Methods

match :: Regex -> String -> String

matchM :: MonadFail m => Regex -> String -> m String

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexMaker Regex CompOption ExecOption ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString

Methods

makeRegex :: ByteString -> Regex

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex

makeRegexM :: MonadFail m => ByteString -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex

RegexMaker Regex CompOption ExecOption ByteString 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex

makeRegexM :: MonadFail m => ByteString -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex

RegexMaker Regex CompOption ExecOption Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text

Methods

makeRegex :: Text -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Text -> Regex

makeRegexM :: MonadFail m => Text -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Text -> m Regex

RegexMaker Regex CompOption ExecOption Text

Since: 1.3.1

Instance details

Defined in Text.Regex.TDFA.Text.Lazy

Methods

makeRegex :: Text -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Text -> Regex

makeRegexM :: MonadFail m => Text -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Text -> m Regex

RegexMaker Regex CompOption ExecOption String 
Instance details

Defined in Text.Regex.TDFA.String

Methods

makeRegex :: String -> Regex

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex

makeRegexM :: MonadFail m => String -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex

RegexMaker Regex CompOption ExecOption (Seq Char) 
Instance details

Defined in Text.Regex.TDFA.Sequence

Methods

makeRegex :: Seq Char -> Regex

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex

makeRegexM :: MonadFail m => Seq Char -> m Regex

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex

RegexLike Regex (Seq Char) 
Instance details

Defined in Text.Regex.TDFA.Sequence

Methods

matchOnce :: Regex -> Seq Char -> Maybe MatchArray

matchAll :: Regex -> Seq Char -> [MatchArray]

matchCount :: Regex -> Seq Char -> Int

matchTest :: Regex -> Seq Char -> Bool

matchAllText :: Regex -> Seq Char -> [MatchText (Seq Char)]

matchOnceText :: Regex -> Seq Char -> Maybe (Seq Char, MatchText (Seq Char), Seq Char)

RegexContext Regex (Seq Char) (Seq Char) 
Instance details

Defined in Text.Regex.TDFA.Sequence

Methods

match :: Regex -> Seq Char -> Seq Char

matchM :: MonadFail m => Regex -> Seq Char -> m (Seq Char)

data WinEmpty Source #

Constructors

WinEmpty Instructions 
WinTest WhichTest (Maybe WinEmpty) (Maybe WinEmpty) 

Instances

Instances details
Show WinEmpty Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> WinEmpty -> ShowS

show :: WinEmpty -> String

showList :: [WinEmpty] -> ShowS

data QNFA Source #

Internal NFA node type.

Constructors

QNFA 

Fields

Instances

Instances details
Show QNFA Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> QNFA -> ShowS

show :: QNFA -> String

showList :: [QNFA] -> ShowS

data QT Source #

Internal to QNFA type.

Constructors

Simple 

Fields

Testing 

Fields

Instances

Instances details
Show QT Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> QT -> ShowS

show :: QT -> String

showList :: [QT] -> ShowS

Eq QT Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

(==) :: QT -> QT -> Bool

(/=) :: QT -> QT -> Bool

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 ($). Also support for GNU extensions is being added: \` beginning of buffer, \' end of buffer, \< and \> for begin and end of words, \b and \B for word boundary and not word boundary.

Constructors

Test_BOL

^ (affected by multiline option)

Test_EOL

$ (affected by multiline option)

Test_BOB

\` beginning of buffer

Test_EOB

\' end ofbuffer

Test_BOW

\< beginning of word

Test_EOW

\> end of word

Test_EdgeWord

\b word boundary

Test_NotEdgeWord

\B not word boundary

Instances

Instances details
Enum WhichTest Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Show WhichTest Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> WhichTest -> ShowS

show :: WhichTest -> String

showList :: [WhichTest] -> ShowS

Eq WhichTest Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

(==) :: WhichTest -> WhichTest -> Bool

(/=) :: WhichTest -> WhichTest -> Bool

Ord WhichTest Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

compare :: WhichTest -> WhichTest -> Ordering

(<) :: WhichTest -> WhichTest -> Bool

(<=) :: WhichTest -> WhichTest -> Bool

(>) :: WhichTest -> WhichTest -> Bool

(>=) :: WhichTest -> WhichTest -> Bool

max :: WhichTest -> WhichTest -> WhichTest

min :: WhichTest -> WhichTest -> WhichTest

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

Instances details
Show TagTask Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> TagTask -> ShowS

show :: TagTask -> String

showList :: [TagTask] -> ShowS

Eq TagTask Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

(==) :: TagTask -> TagTask -> Bool

(/=) :: TagTask -> TagTask -> Bool

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.

Instances

Instances details
Show TagUpdate Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> TagUpdate -> ShowS

show :: TagUpdate -> String

showList :: [TagUpdate] -> ShowS

Eq TagUpdate Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

(==) :: TagUpdate -> TagUpdate -> Bool

(/=) :: TagUpdate -> TagUpdate -> Bool

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 = TagList Source #

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

Instances

Instances details
Show DFA Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> DFA -> ShowS

show :: DFA -> String

showList :: [DFA] -> ShowS

data Transition Source #

Constructors

Transition 

Fields

data DT Source #

Internal to the DFA node

Constructors

Simple' 

Fields

Testing' 

Fields

Instances

Instances details
Show DT Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> DT -> ShowS

show :: DT -> String

showList :: [DT] -> ShowS

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

Internal type to represent 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.

A Destination IntMap entry may have an empty Source IntMap if and only if the destination is the starting index and the NFA or DFA. This instructs the matching engine to spawn a new entry starting at the post-update position.

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 at back but compare starting with front, so use Seq as a queue. The initial position is saved in basePos (and a Maximize Tag), the middle positions in the Seq, and the final position is NOT saved in the Orbits (only in a Maximize Tag).

Constructors

Orbits 

Fields

Instances

Instances details
Show Orbits Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> Orbits -> ShowS

show :: Orbits -> String

showList :: [Orbits] -> ShowS

data Instructions Source #

The newPos and newFlags lists in Instructions are sorted by, and unique in, the Tag values

Constructors

Instructions 

Fields

Instances

Instances details
Show Instructions Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> Instructions -> ShowS

show :: Instructions -> String

showList :: [Instructions] -> ShowS

data Action Source #

Constructors

SetPre 
SetPost 
SetVal Int 

Instances

Instances details
Show Action Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

showsPrec :: Int -> Action -> ShowS

show :: Action -> String

showList :: [Action] -> ShowS

Eq Action Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Methods

(==) :: Action -> Action -> Bool

(/=) :: Action -> Action -> Bool

type OrbitLog = IntMap Orbits Source #

showQT :: QT -> String Source #

indent :: [String] -> String Source #

showDT :: DT -> String Source #

seeDTrans :: DTrans -> String Source #