| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
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
- look :: Int -> IntMap a -> a
- common_error :: String -> String -> a
- on :: (t1 -> t1 -> t2) -> (t -> t1) -> t -> t -> t2
- norep :: Eq a => [a] -> [a]
- norepBy :: (a -> a -> Bool) -> [a] -> [a]
- mapFst :: Functor f => (t -> t2) -> f (t, t1) -> f (t2, t1)
- mapSnd :: Functor f => (t1 -> t2) -> f (t, t1) -> f (t, t2)
- fst3 :: (a, b, c) -> a
- snd3 :: (a, b, c) -> b
- thd3 :: (a, b, c) -> c
- flipOrder :: Ordering -> Ordering
- noWin :: WinTags -> Bool
- newtype DoPa = DoPa {}
- data CompOption = CompOption {- caseSensitive :: Bool
- multiline :: Bool
- rightAssoc :: Bool
- newSyntax :: Bool
- lastStarGreedy :: Bool
 
- data ExecOption = ExecOption {}
- type Tag = Int
- data OP
- type Index = Int
- type SetIndex = IntSet
- type Position = Int
- type GroupIndex = Int
- data GroupInfo = GroupInfo {- thisIndex, parentIndex :: GroupIndex
- startTag, stopTag, flagTag :: Tag
 
- data Regex = Regex {}
- data WinEmpty
- data QNFA = QNFA {}
- data QT
- type QTrans = IntMap [TagCommand]
- data WhichTest
- data TagTask
- type TagTasks = [(Tag, TagTask)]
- data TagUpdate
- type TagList = [(Tag, TagUpdate)]
- type TagCommand = (DoPa, TagList)
- type WinTags = TagList
- data DFA = DFA {}
- data Transition = Transition {- trans_many :: DFA
- trans_single :: DFA
- trans_how :: DTrans
 
- data DT
- type DTrans = IntMap (IntMap (DoPa, Instructions))
- type DTrans' = [(Index, [(Index, (DoPa, ([(Tag, (Position, Bool))], [String])))])]
- data Orbits = Orbits {}
- data Instructions = Instructions {}
- data Action
- type OrbitTransformer = OrbitLog -> OrbitLog
- type OrbitLog = IntMap Orbits
- showQT :: QT -> String
- indent :: [String] -> String
- showDT :: DT -> String
- seeDTrans :: DTrans -> String
Documentation
common_error :: String -> String -> a Source #
Used to track elements of the pattern that accept characters or are anchors.
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 
 | |
Instances
data ExecOption Source #
Constructors
| ExecOption | |
| Fields 
 | |
Instances
Used by implementation to name certain Postions during
 matching. Identity of Position tag to set during a transition.
Internal use to indicate type of tag and preference for larger or smaller Positions.
type GroupIndex = Int Source #
GroupIndex is for indexing submatches from capturing parenthesized groups (PGroup or Group).
GroupInfo collects the parent and tag information for an instance of a group.
Constructors
| GroupInfo | |
| Fields 
 | |
The TDFA backend specific Regex type, used by this module's RegexOptions and RegexMaker.
Constructors
| Regex | |
| Fields 
 | |
Instances
Internal NFA node type.
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.
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 | 
 | 
| Test_EOL | 
 | 
| Test_BOB | 
 | 
| Test_EOB | 
 | 
| Test_BOW | 
 | 
| Test_EOW | 
 | 
| Test_EdgeWord | 
 | 
| Test_NotEdgeWord | 
 | 
Instances
| Enum WhichTest Source # | |
| Defined in Text.Regex.TDFA.Common Methods succ :: WhichTest -> WhichTest # pred :: WhichTest -> WhichTest # fromEnum :: WhichTest -> Int # enumFrom :: WhichTest -> [WhichTest] # enumFromThen :: WhichTest -> WhichTest -> [WhichTest] # enumFromTo :: WhichTest -> WhichTest -> [WhichTest] # enumFromThenTo :: WhichTest -> WhichTest -> WhichTest -> [WhichTest] # | |
| Show WhichTest Source # | |
| Eq WhichTest Source # | |
| Ord WhichTest 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.
Constructors
| TagTask | |
| ResetGroupStopTask | |
| SetGroupStopTask | |
| ResetOrbitTask | |
| EnterOrbitTask | |
| LeaveOrbitTask | 
Instances
When attached to a QTrans the TagTask can be done before or after accepting the character.
Constructors
| PreUpdate TagTask | |
| PostUpdate TagTask | 
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.
Internal DFA node, identified by the Set of indices of the QNFA nodes it represents.
data Transition Source #
Constructors
| Transition | |
| Fields 
 | |
Internal to the DFA node
Constructors
| Simple' | |
| Fields 
 | |
| Testing' | |
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.
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 | |
data Instructions Source #
The newPos and newFlags lists in Instructions are sorted by, and unique in, the Tag values
Constructors
| Instructions | |
Instances
| Show Instructions Source # | |
| Defined in Text.Regex.TDFA.Common Methods showsPrec :: Int -> Instructions -> ShowS # show :: Instructions -> String # showList :: [Instructions] -> ShowS # | |
type OrbitTransformer = OrbitLog -> OrbitLog Source #