Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.RE.PCRE.RE
Contents
- data RE
- regexType :: RegexType
- reOptions :: RE -> REOptions
- reSource :: RE -> String
- reCaptureNames :: RE -> CaptureNames
- reRegex :: RE -> Regex
- type REOptions = REOptions_ RE CompOption ExecOption
- defaultREOptions :: REOptions
- noPreludeREOptions :: REOptions
- compileRegex :: (Functor m, Monad m) => String -> m RE
- compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> String -> m RE
- compileRegexWithOptions :: (IsOption o RE CompOption ExecOption, Functor m, Monad m) => o -> String -> m RE
- compileSearchReplace :: (Monad m, Functor m, IsRegex RE s) => String -> String -> m (SearchReplace RE s)
- compileSearchReplaceWith :: (Monad m, Functor m, IsRegex RE s) => SimpleREOptions -> String -> String -> m (SearchReplace RE s)
- compileSearchReplaceWithREOptions :: (Monad m, Functor m, IsRegex RE s) => REOptions -> String -> String -> m (SearchReplace RE s)
- escape :: (Functor m, Monad m) => (String -> String) -> String -> m RE
- escapeWith :: (Functor m, Monad m) => SimpleREOptions -> (String -> String) -> String -> m RE
- escapeWithOptions :: (IsOption o RE CompOption ExecOption, Functor m, Monad m) => o -> (String -> String) -> String -> m RE
- escapeREString :: String -> String
- prelude :: Macros RE
- preludeEnv :: MacroEnv
- preludeTestsFailing :: [MacroID]
- preludeTable :: String
- preludeSummary :: PreludeMacro -> String
- preludeSources :: String
- preludeSource :: PreludeMacro -> String
- unpackSimpleREOptions :: SimpleREOptions -> REOptions
- re :: QuasiQuoter
- reMS :: QuasiQuoter
- reMI :: QuasiQuoter
- reBS :: QuasiQuoter
- reBI :: QuasiQuoter
- reMultilineSensitive :: QuasiQuoter
- reMultilineInsensitive :: QuasiQuoter
- reBlockSensitive :: QuasiQuoter
- reBlockInsensitive :: QuasiQuoter
- re_ :: QuasiQuoter
- cp :: QuasiQuoter
RE Type
the RE type for this back end representing a well-formed, compiled RE
Instances
regexType :: RegexType Source #
some functions in the Text.RE.TestBench need the back end to
be passed dynamically as a RegexType
parameters: use regexType
fpr this backend
reCaptureNames :: RE -> CaptureNames Source #
extract the CaptureNames
from the RE
REOptions Type
type REOptions = REOptions_ RE CompOption ExecOption Source #
and the REOptions for this back end (see Text.RE.Types.REOptions for details)
defaultREOptions :: REOptions Source #
the default REOptions
noPreludeREOptions :: REOptions Source #
the default REOptions
but with no RE macros defined
Compiling Regular Expressions
compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> String -> m RE Source #
compileRegexWithOptions :: (IsOption o RE CompOption ExecOption, Functor m, Monad m) => o -> String -> m RE Source #
Compiling Search-Replace Templates
compileSearchReplace :: (Monad m, Functor m, IsRegex RE s) => String -> 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
compileSearchReplaceWith :: (Monad m, Functor m, IsRegex RE s) => SimpleREOptions -> String -> String -> m (SearchReplace RE s) Source #
compile a SearchReplace template, with simple options, generating errors if the RE or the template are not well formed -- all capture references being checked
compileSearchReplaceWithREOptions :: (Monad m, Functor m, IsRegex RE s) => REOptions -> String -> String -> m (SearchReplace RE s) Source #
compile a SearchReplace template, with general options, generating errors if the RE or the template are not well formed -- all capture references being checked
Escaping String
escape :: (Functor m, Monad m) => (String -> String) -> String -> m RE Source #
convert a string into a RE that matches that string, and apply it to an argument continuation function to make up the RE string to be compiled
escapeWith :: (Functor m, Monad m) => SimpleREOptions -> (String -> String) -> String -> m RE Source #
convert a string into a RE that matches that string, and apply it to an argument continuation function to make up the RE string to be compiled with the default options
escapeWithOptions :: (IsOption o RE CompOption ExecOption, Functor m, Monad m) => o -> (String -> String) -> String -> m RE Source #
convert a string into a RE that matches that string, and apply it to an argument continuation function to make up the RE string to be compiled the given options
escapeREString :: String -> String #
Convert a string into a regular expression that will amtch that string
Macros Standard Environment
preludeSummary :: PreludeMacro -> String Source #
preludeSource :: PreludeMacro -> String Source #
unpackSimpleREOptions :: SimpleREOptions -> REOptions Source #
convert a universal SimpleReOptions
into the REOptions
used
by this back end
The Quasi Quoters
re :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reMS :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reMI :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reBS :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reBI :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reMultilineSensitive :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reMultilineInsensitive :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reBlockSensitive :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
reBlockInsensitive :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
re_ :: QuasiQuoter Source #
the [re| ... |]
and [ed| ... /// ... |]
quasi quoters
cp :: QuasiQuoter #
quasi quoter for CaptureID ([cp|0|],[cp|y|], etc.)