Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type MacroEnv = HashMap MacroID MacroDescriptor
- data MacroDescriptor = MacroDescriptor {
- macroSource :: !RegexSource
- macroSamples :: ![String]
- macroCounterSamples :: ![String]
- macroTestResults :: ![TestResult]
- macroParser :: !(Maybe FunctionID)
- macroDescription :: !String
- newtype RegexSource = RegexSource {}
- data WithCaptures
- data RegexType
- isTDFA :: RegexType -> Bool
- isPCRE :: RegexType -> Bool
- presentRegexType :: RegexType -> String
- mkMacros :: (Monad m, Functor m) => (String -> m r) -> RegexType -> WithCaptures -> MacroEnv -> m (Macros r)
- formatMacroTable :: RegexType -> MacroEnv -> String
- formatMacroSummary :: RegexType -> MacroEnv -> MacroID -> String
- formatMacroSources :: RegexType -> WithCaptures -> MacroEnv -> String
- formatMacroSource :: RegexType -> WithCaptures -> MacroEnv -> MacroID -> String
- mdRegexSource :: RegexType -> WithCaptures -> MacroEnv -> MacroDescriptor -> String
- testMacroEnv :: String -> RegexType -> MacroEnv -> IO Bool
- runTests :: (Eq a, Show a) => RegexType -> (String -> Maybe a) -> [(String, a)] -> MacroEnv -> MacroID -> MacroDescriptor -> MacroDescriptor
- runTests' :: (Eq a, Show a) => RegexType -> (Match String -> Maybe a) -> [(String, a)] -> MacroEnv -> MacroID -> MacroDescriptor -> MacroDescriptor
- module Text.RE.TestBench.Parsers
- data Match a
The Test Bench Tutorial
This API module provides a test bench for developing, documenting and testing regex RE macros.
See the tutorials at http://re-tutorial-testbench.regex.uk
The Test Bench
type MacroEnv = HashMap MacroID MacroDescriptor Source #
each macro can reference others, the whole environment being required for each macro, so we use a Lazy HashMap
data MacroDescriptor Source #
describes a macro, giving the text of the RE and a si=ummary description
MacroDescriptor | |
|
Instances
Show MacroDescriptor Source # | |
Defined in Text.RE.ZeInternals.TestBench showsPrec :: Int -> MacroDescriptor -> ShowS # show :: MacroDescriptor -> String # showList :: [MacroDescriptor] -> ShowS # |
newtype RegexSource Source #
a RE that should work for POSIX and PCRE with open brackets ('(') represented as follows: ( mere symbol (?: used for grouping only, not for captures (}: used for captures only, not for grouping (]: used for captures and grouping ( do not modify
Instances
Show RegexSource Source # | |
Defined in Text.RE.ZeInternals.TestBench showsPrec :: Int -> RegexSource -> ShowS # show :: RegexSource -> String # showList :: [RegexSource] -> ShowS # | |
IsString RegexSource Source # | |
Defined in Text.RE.ZeInternals.TestBench fromString :: String -> RegexSource # |
data WithCaptures Source #
do we need the captures in the RE or whould they be stripped out where possible
InclCaptures | include all captures |
ExclCaptures | remove captures where possible |
Instances
Eq WithCaptures Source # | |
Defined in Text.RE.ZeInternals.TestBench (==) :: WithCaptures -> WithCaptures -> Bool # (/=) :: WithCaptures -> WithCaptures -> Bool # | |
Ord WithCaptures Source # | |
Defined in Text.RE.ZeInternals.TestBench compare :: WithCaptures -> WithCaptures -> Ordering # (<) :: WithCaptures -> WithCaptures -> Bool # (<=) :: WithCaptures -> WithCaptures -> Bool # (>) :: WithCaptures -> WithCaptures -> Bool # (>=) :: WithCaptures -> WithCaptures -> Bool # max :: WithCaptures -> WithCaptures -> WithCaptures # min :: WithCaptures -> WithCaptures -> WithCaptures # | |
Show WithCaptures Source # | |
Defined in Text.RE.ZeInternals.TestBench showsPrec :: Int -> WithCaptures -> ShowS # show :: WithCaptures -> String # showList :: [WithCaptures] -> ShowS # |
what flavour of regex are we dealing with
presentRegexType :: RegexType -> String Source #
Constructing a MacrosEnv
mkMacros :: (Monad m, Functor m) => (String -> m r) -> RegexType -> WithCaptures -> MacroEnv -> m (Macros r) Source #
construct a macro table suitable for use with the RE compilers
Formatting Macros
formatMacroTable :: RegexType -> MacroEnv -> String Source #
format a macros table as a markdown table
formatMacroSummary :: RegexType -> MacroEnv -> MacroID -> String Source #
generate a plain text summary of a macro
formatMacroSources :: RegexType -> WithCaptures -> MacroEnv -> String Source #
list the source REs for each macro in plain text
formatMacroSource :: RegexType -> WithCaptures -> MacroEnv -> MacroID -> String Source #
list the source of a single macro in plain text
mdRegexSource :: RegexType -> WithCaptures -> MacroEnv -> MacroDescriptor -> String Source #
Formatting Macros
testMacroEnv :: String -> RegexType -> MacroEnv -> IO Bool Source #
test that a MacroEnv is passing all of its built-in tests
runTests :: (Eq a, Show a) => RegexType -> (String -> Maybe a) -> [(String, a)] -> MacroEnv -> MacroID -> MacroDescriptor -> MacroDescriptor Source #
runTests' :: (Eq a, Show a) => RegexType -> (Match String -> Maybe a) -> [(String, a)] -> MacroEnv -> MacroID -> MacroDescriptor -> MacroDescriptor Source #
The Parsers
module Text.RE.TestBench.Parsers
The Match Type
the result of matching a RE to a text once (with ?=~
), retaining
the text that was matched against
Instances
Functor Match Source # | |
(RegexContext regex source (AllTextSubmatches (Array Int) (source, (Int, Int))), RegexLike regex source, RegexFix regex source) => RegexContext regex source (Match source) Source # | this instance hooks |
Eq a => Eq (Match a) Source # | |
Show a => Show (Match a) Source # | |