Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- addCaptureNames :: Typeable a => CaptureNames -> a -> a
- addCaptureNamesToMatches :: CaptureNames -> Matches a -> Matches a
- addCaptureNamesToMatch :: CaptureNames -> Match a -> Match a
- escapeREString :: String -> String
- cp :: QuasiQuoter
- extractNamedCaptures :: String -> Either String ((Int, CaptureNames), String)
- idFormatTokenREOptions :: FormatTokenREOptions
- data Token
- validToken :: Token -> Bool
- formatTokens :: [Token] -> String
- formatTokens' :: FormatTokenREOptions -> [Token] -> String
- formatTokens0 :: [Token] -> String
- scan :: String -> [Token]
- expandMacros :: (r -> String) -> Macros r -> String -> String
- data PreludeMacro
- presentPreludeMacro :: PreludeMacro -> String
- preludeMacros :: (Monad m, Functor m) => (String -> m r) -> RegexType -> WithCaptures -> m (Macros r)
- preludeMacroTable :: RegexType -> String
- preludeMacroSummary :: RegexType -> PreludeMacro -> String
- preludeMacroSources :: RegexType -> String
- preludeMacroSource :: RegexType -> PreludeMacro -> String
- preludeMacroEnv :: RegexType -> MacroEnv
- unsafeCompileSearchReplace_ :: (String -> s) -> (String -> Either String re) -> String -> SearchReplace re s
- compileSearchReplace_ :: (Monad m, MonadFail m, Functor m) => (String -> s) -> (String -> Either String re) -> String -> m (SearchReplace re s)
- compileSearchAndReplace_ :: (Monad m, MonadFail m, Functor m) => (String -> s) -> (String -> Either String re) -> String -> String -> m (SearchReplace re s)
- data QQFailure = QQFailure {}
- qq0 :: String -> QuasiQuoter
- mkTDFA :: TestBenchMatcher -> RegexType
- mkPCRE :: TestBenchMatcher -> RegexType
- badMacros :: MacroEnv -> [MacroID]
The regex Internal Modules
This module contains just what the test suite (re-tests) in regex-examples needs from the package internals to do its job and the ZeInternals types and functions needed by the regex-with-pcre package
Text.RE.ZeInternals.AddCaptureNames
addCaptureNames :: Typeable a => CaptureNames -> a -> a Source #
a hairy dynamically-typed function used with the legacy (=~) and (=~~) to see if it can/should add the capture names extracted from the RE into the polymorphic result of the operator (it does for any Match or Matches type, provided it is parameterised over a recognised type). The test suite is all over this one, testing all of these cases.
addCaptureNamesToMatches :: CaptureNames -> Matches a -> Matches a Source #
a convenience function used by the API modules to insert capture names extracted from the parsed RE into the (*=~) result
addCaptureNamesToMatch :: CaptureNames -> Match a -> Match a Source #
a convenience function used by the API modules to insert capture names extracted from the parsed RE into the (?=~) result
Text.RE.ZeInternals.EscapeREString
escapeREString :: String -> String Source #
Convert a string into a regular expression that will match that string
Text.RE.ZeInternals.NamedCaptures
cp :: QuasiQuoter Source #
quasi quoter for CaptureID: [cp|0|]
, [cp|0|]
, etc.,
indexing captures by classic positional numbers, and [cp|foo|]
,
etc., referencing a named capture [re| ... ${foo}( ... ) ... |]
.
extractNamedCaptures :: String -> Either String ((Int, CaptureNames), String) Source #
extract the CaptureNames from an RE or return an error diagnostic if the RE is not well formed; also returs the total number of captures in the RE
idFormatTokenREOptions :: FormatTokenREOptions Source #
a configuration that will preserve the parsed regular expression in the output
our RE scanner returns a list of these tokens
Instances
Eq Token Source # | |
Show Token Source # | |
Generic Token Source # | |
type Rep Token Source # | |
Defined in Text.RE.ZeInternals.NamedCaptures type Rep Token = D1 (MetaData "Token" "Text.RE.ZeInternals.NamedCaptures" "regex-1.1.0.0-9uTzK5r667kuTaOAe53le" False) ((C1 (MetaCons "ECap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) :+: (C1 (MetaCons "PGrp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PCap" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Bra" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) :+: C1 (MetaCons "Other" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))))) |
validToken :: Token -> Bool Source #
check that a token is well formed
formatTokens :: [Token] -> String Source #
format [Token] into an RE string
formatTokens' :: FormatTokenREOptions -> [Token] -> String Source #
the general Token formatter, generating REs according to the options
formatTokens0 :: [Token] -> String Source #
Text.RE.ZeInternals.Replace
expandMacros :: (r -> String) -> Macros r -> String -> String Source #
expand all of the @{..} macros in the RE in the argument String according to the Macros argument, preprocessing the RE String according to the Mode argument (used internally)
Text.RE.ZeInternals.PreludeMacros
data PreludeMacro Source #
an enumeration of all of the prelude macros
Instances
presentPreludeMacro :: PreludeMacro -> String Source #
naming the macros
preludeMacros :: (Monad m, Functor m) => (String -> m r) -> RegexType -> WithCaptures -> m (Macros r) Source #
generate the standard prelude Macros used to parse REs
preludeMacroTable :: RegexType -> String Source #
format the standard prelude macros in a markdown table
preludeMacroSummary :: RegexType -> PreludeMacro -> String Source #
generate a textual summary of the prelude macros
preludeMacroSources :: RegexType -> String Source #
generate a plain text table giving the RE for each macro with all macros expanded (to NF)
preludeMacroSource :: RegexType -> PreludeMacro -> String Source #
generate plain text giving theexpanded RE for a single macro
preludeMacroEnv :: RegexType -> MacroEnv Source #
generate the MacroEnv
for the standard prelude macros
Text.RE.ZeInternals.SearchReplace
unsafeCompileSearchReplace_ :: (String -> s) -> (String -> Either String re) -> String -> SearchReplace re s Source #
warapper on compileSearchReplace_
that will generate an error
if any compilation errors are found
compileSearchReplace_ :: (Monad m, MonadFail m, Functor m) => (String -> s) -> (String -> Either String re) -> String -> m (SearchReplace re s) Source #
compile a SearchReplace template generating errors if the RE or the template are not well formed -- all capture references being checked
compileSearchAndReplace_ :: (Monad m, MonadFail m, Functor m) => (String -> s) -> (String -> Either String re) -> String -> String -> m (SearchReplace re s) Source #
compile SearcgReplace
from two strings containing the RE
and the replacement template
Text.RE.ZeInternals.QQ
used to throw an exception reporting an abuse of a quasi quoter
QQFailure | |
|
Instances
Show QQFailure Source # | |
Exception QQFailure Source # | |
Defined in Text.RE.ZeInternals.QQ toException :: QQFailure -> SomeException # fromException :: SomeException -> Maybe QQFailure # displayException :: QQFailure -> String # |
qq0 :: String -> QuasiQuoter Source #
a quasi quoter that can be used in no context (to be extended with the appropriate quasi quoter parser)