Safe Haskell | None |
---|---|
Language | Haskell2010 |
- Tutorial
- About this Module
- The
Matches
andMatch
Operators - The
SearchReplace
Operators - The
Matches
Type - The
Match
Type - The Macros and Parsers
- The
RE
Type - Options
- Compiling and Escaping REs
- The Classic regex-base Match Operators
- The re Quasi Quoters
- The Ed Quasi Quoters
- The cp Quasi Quoters
- RE Macros Standard Environment
- IsRegex
- The IsRegex Instances
Synopsis
- (*=~) :: IsRegex RE s => s -> RE -> Matches s
- (?=~) :: IsRegex RE s => s -> RE -> Match s
- (*=~/) :: IsRegex RE s => s -> SearchReplace RE s -> s
- (?=~/) :: IsRegex RE s => s -> SearchReplace RE s -> s
- data Matches a
- matchesSource :: Matches a -> a
- allMatches :: Matches a -> [Match a]
- anyMatches :: Matches a -> Bool
- countMatches :: Matches a -> Int
- matches :: Matches a -> [a]
- data Match a
- matchSource :: Match a -> a
- matched :: Match a -> Bool
- matchedText :: Match a -> Maybe a
- module Text.RE.TestBench.Parsers
- data RE
- regexType :: RegexType
- reOptions :: RE -> REOptions
- reSource :: RE -> String
- reCaptureNames :: RE -> CaptureNames
- reRegex :: RE -> Regex
- data SimpleREOptions
- class IsOption o where
- makeREOptions :: o -> REOptions
- type REOptions = REOptions_ RE CompOption ExecOption
- defaultREOptions :: REOptions
- noPreludeREOptions :: REOptions
- unpackSimpleREOptions :: SimpleREOptions -> REOptions
- data SearchReplace re s = SearchReplace {
- getSearch :: !re
- getTemplate :: !s
- compileRegex :: (Functor m, Monad m, MonadFail m) => String -> m RE
- compileRegexWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> String -> m RE
- compileRegexWithOptions :: (IsOption o, Functor m, Monad m, MonadFail m) => o -> String -> m RE
- compileSearchReplace :: (Monad m, MonadFail m, Functor m, IsRegex RE s) => String -> String -> m (SearchReplace RE s)
- compileSearchReplaceWith :: (Monad m, MonadFail m, Functor m, IsRegex RE s) => SimpleREOptions -> String -> String -> m (SearchReplace RE s)
- compileSearchReplaceWithOptions :: (Monad m, MonadFail m, Functor m, IsRegex RE s) => REOptions -> String -> String -> m (SearchReplace RE s)
- escape :: (Functor m, Monad m, MonadFail m) => (String -> String) -> String -> m RE
- escapeWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> (String -> String) -> String -> m RE
- escapeWithOptions :: (IsOption o, Functor m, Monad m, MonadFail m) => o -> (String -> String) -> String -> m RE
- escapeREString :: String -> String
- (=~) :: (RegexContext Regex s a, RegexMaker Regex CompOption ExecOption s) => s -> RE -> a
- (=~~) :: (Monad m, MonadFail m, RegexContext Regex s a, RegexMaker Regex CompOption ExecOption s) => s -> RE -> m a
- re :: QuasiQuoter
- reMultilineSensitive :: QuasiQuoter
- reMultilineInsensitive :: QuasiQuoter
- reBlockSensitive :: QuasiQuoter
- reBlockInsensitive :: QuasiQuoter
- reMS :: QuasiQuoter
- reMI :: QuasiQuoter
- reBS :: QuasiQuoter
- reBI :: QuasiQuoter
- re_ :: QuasiQuoter
- ed :: QuasiQuoter
- edMultilineSensitive :: QuasiQuoter
- edMultilineInsensitive :: QuasiQuoter
- edBlockSensitive :: QuasiQuoter
- edBlockInsensitive :: QuasiQuoter
- edMS :: QuasiQuoter
- edMI :: QuasiQuoter
- edBS :: QuasiQuoter
- edBI :: QuasiQuoter
- ed_ :: QuasiQuoter
- cp :: QuasiQuoter
- prelude :: Macros RE
- preludeEnv :: MacroEnv
- preludeTestsFailing :: [MacroID]
- preludeTable :: String
- preludeSummary :: PreludeMacro -> String
- preludeSources :: String
- preludeSource :: PreludeMacro -> String
- module Text.RE.Tools.IsRegex
Tutorial
We have a regex tutorial at http://tutorial.regex.uk.
About this Module
This module provides access to the back end through polymorphic functions that operate over all of the String/Text/ByteString types supported by the back end. The module also provides all of the specialised back-end functionality that will not be needed by most regex clients. If you don't need this generality then you might want to consider using one of the simpler modules that have been specialised for each of these types:
The Matches
and Match
Operators
(*=~) :: IsRegex RE s => s -> RE -> Matches s Source #
find all the matches in the argument text; e.g., to count the number of naturals in s:
countMatches $ s *=~ [re|[0-9]+|]
(?=~) :: IsRegex RE s => s -> RE -> Match s Source #
find the first match in the argument text; e.g., to test if there is a natural number in the input text:
matched $ s ?=~ [re|[0-9]+|]
The SearchReplace
Operators
(*=~/) :: IsRegex RE s => s -> SearchReplace RE s -> s Source #
search and replace all matches in the argument text; e.g., this section will convert every YYYY-MM-DD format date in its argument text into a DD/MM/YYYY date:
(*=~/ [ed|${y}([0-9]{4})-0*${m}([0-9]{2})-0*${d}([0-9]{2})///${d}/${m}/${y}|])
(?=~/) :: IsRegex RE s => s -> SearchReplace RE s -> s Source #
search and replace the first occurrence only
The Matches
Type
the result of matching a RE against a text (with *=~
), retaining
the text that was matched against
Instances
Functor Matches Source # | |
(RegexContext regex source [MatchText source], RegexLike regex source, RegexFix regex source) => RegexContext regex source (Matches source) Source # | this instance hooks |
Eq a => Eq (Matches a) Source # | |
Show a => Show (Matches a) Source # | |
matchesSource :: Matches a -> a Source #
the source text being matched
anyMatches :: Matches a -> Bool Source #
tests whether the RE matched the source text at all
countMatches :: Matches a -> Int Source #
count the matches
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 # | |
matchSource :: Match a -> a Source #
the whole source text
matchedText :: Match a -> Maybe a Source #
yields the text matched by the RE, Nothing if no match
The Macros and Parsers
There are a number of RE macros and corresponding Haskell parsers for parsing the matched text into appropriate Haskell types. See the Macros Tables for details.
module Text.RE.TestBench.Parsers
The 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
for this
reCaptureNames :: RE -> CaptureNames Source #
extract the CaptureNames
from the RE
Options
You can specify different compilation options by appending a to the name of an [re| ... |] or [ed| ... /// ... |] quasi quoter to select the corresponding compilation option. For example, the section,
(?=~/ [edBlockInsensitive|foo$///bar|])
will replace a foo
suffix of the argument text, of any
capitalisation, with a (lower case) bar
. If you need to specify the
options dynamically, use the [re_| ... |]
and [ed_| ... /// ... |]
quasi quoters, which generate functions that take an IsOption
option
(e.g., a SimpleReOptions
value) and yields a RE
or SearchReplace
as appropriate. For example if you have a SimpleReOptions
value in
sro
then
(?=~/ [ed_|foo$///bar|] sro)
will compile the foo$
RE according to the value of sro
. For more
on specifying RE options see Text.RE.REOptions.
data SimpleREOptions Source #
the default API uses these simple, universal RE options,
which get auto-converted into the appropriate back-end REOptions_
MultilineSensitive | case-sensitive with ^ and $ matching the start and end of a line |
MultilineInsensitive | case-insensitive with ^ and $ matsh the start and end of a line |
BlockSensitive | case-sensitive with ^ and $ matching the start and end of the input text |
BlockInsensitive | case-insensitive with ^ and $ matching the start and end of the input text |
Instances
class IsOption o where Source #
a number of types can be used to encode REOptions_
, each of which
is made a member of this class
makeREOptions :: o -> REOptions Source #
convert the o
type into an REOptions
Instances
IsOption () Source # | |
Defined in Text.RE.ZeInternals.TDFA makeREOptions :: () -> REOptions Source # | |
IsOption CompOption Source # | |
Defined in Text.RE.ZeInternals.TDFA makeREOptions :: CompOption -> REOptions Source # | |
IsOption ExecOption Source # | |
Defined in Text.RE.ZeInternals.TDFA makeREOptions :: ExecOption -> REOptions Source # | |
IsOption SimpleREOptions Source # | |
Defined in Text.RE.ZeInternals.TDFA | |
IsOption REOptions Source # | |
Defined in Text.RE.ZeInternals.TDFA makeREOptions :: REOptions -> REOptions Source # | |
IsOption (Macros RE) Source # | |
Defined in Text.RE.ZeInternals.TDFA |
type REOptions = REOptions_ RE CompOption ExecOption Source #
and the REOptions for this back end (see Text.RE.REOptions for details)
defaultREOptions :: REOptions Source #
the default REOptions
noPreludeREOptions :: REOptions Source #
the default REOptions
but with no RE macros defined
unpackSimpleREOptions :: SimpleREOptions -> REOptions Source #
convert a universal SimpleReOptions
into the REOptions
used
by this back end
Compiling and Escaping REs
data SearchReplace re s Source #
contains a compiled RE and replacement template
SearchReplace | |
|
Instances
Functor (SearchReplace re) Source # | |
Defined in Text.RE.ZeInternals.Types.SearchReplace fmap :: (a -> b) -> SearchReplace re a -> SearchReplace re b # (<$) :: a -> SearchReplace re b -> SearchReplace re a # | |
(Show re, Show s) => Show (SearchReplace re s) Source # | |
Defined in Text.RE.ZeInternals.Types.SearchReplace showsPrec :: Int -> SearchReplace re s -> ShowS # show :: SearchReplace re s -> String # showList :: [SearchReplace re s] -> ShowS # |
compileRegexWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> String -> m RE Source #
compileRegexWithOptions :: (IsOption o, Functor m, Monad m, MonadFail m) => o -> String -> m RE Source #
compileSearchReplace :: (Monad m, MonadFail 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, MonadFail 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
compileSearchReplaceWithOptions :: (Monad m, MonadFail 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
escape :: (Functor m, Monad m, MonadFail 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; e.g., to compile a RE that will only match the string:
maybe undefined id . escape (("^"++) . (++"$"))
escapeWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> (String -> String) -> String -> m RE Source #
a variant of escape
where the SimpleREOptions
are specified
escapeWithOptions :: (IsOption o, Functor m, Monad m, MonadFail m) => o -> (String -> String) -> String -> m RE Source #
a variant of escapeWith
that allows an IsOption
RE option
to be specified
escapeREString :: String -> String Source #
Convert a string into a regular expression that will match that string
The Classic regex-base Match Operators
(=~) :: (RegexContext Regex s a, RegexMaker Regex CompOption ExecOption s) => s -> RE -> a Source #
the regex-base polymorphic match operator
(=~~) :: (Monad m, MonadFail m, RegexContext Regex s a, RegexMaker Regex CompOption ExecOption s) => s -> RE -> m a Source #
the regex-base monadic, polymorphic match operator
The re Quasi Quoters
The [re|.*|]
quasi quoters, with variants for specifying different
options to the RE compiler (see Text.RE.REOptions), and the
specialised back-end types and functions.
re :: QuasiQuoter Source #
[re| ... |]
, is equivalent to [reMultilineSensitive| ... |]
,
compiling a case-sensitive, multi-line RE
reMultilineSensitive :: QuasiQuoter Source #
[reMultilineSensitive| ... |]
, compiles a case-sensitive, multi-line RE
reMultilineInsensitive :: QuasiQuoter Source #
[reMultilineInsensitive| ... |]
, compiles a case-insensitive, multi-line RE
reBlockSensitive :: QuasiQuoter Source #
[reMultilineInsensitive| ... |]
, compiles a case-sensitive, non-multi-line RE
reBlockInsensitive :: QuasiQuoter Source #
[reMultilineInsensitive| ... |]
, compiles a case-insensitive, non-multi-line RE
reMS :: QuasiQuoter Source #
[reMS| ... |]
is a shorthand for [reMultilineSensitive| ... |]
reMI :: QuasiQuoter Source #
[reMI| ... |]
is a shorthand for [reMultilineInsensitive| ... |]
reBS :: QuasiQuoter Source #
[reBS| ... |]
is a shorthand for [reBlockSensitive| ... |]
reBI :: QuasiQuoter Source #
[reBI| ... |]
is a shorthand for [reBlockInsensitive| ... |]
re_ :: QuasiQuoter Source #
[re_| ... |]
compiles a RE to produce a function that takes
the RE options (e.g., a SimpleREOptions
value) and yields the
RE compiled with those options. For example,
countMatches $ s *=~ [re_|[0-9a-f]+|] MultilineInsensitive
counts the number of hexadecimal digit strings in s
, allowing
for upper- or lower-case hex digits (which is entirely equivalent
in this example to just using [reMultilineInsensitive|[0-9a-f]+|]
).
The Ed Quasi Quoters
The -- | the [ed| ... /// ... |]
quasi quoters; for example,
[ed|${y}([0-9]{4})-0*${m}([0-9]{2})-0*${d}([0-9]{2})///${d}/${m}/${y}|])
represents a SearchReplace
that will convert a YYYY-MM-DD format date
into a DD/MM/YYYY format date.
The only difference between these quasi quoters is the RE options that are set,
using the same conventions as the [re| ... |]
quasi quoters.
ed :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edMultilineSensitive :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edMultilineInsensitive :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edBlockSensitive :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edBlockInsensitive :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edMS :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edMI :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edBS :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
edBI :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
ed_ :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters
The cp Quasi Quoters
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}( ... ) ... |]
.
RE Macros Standard Environment
the standard table of Macros
used to compile REs (which can be
extended or replace: see Text.RE.TestBench)
preludeEnv :: MacroEnv Source #
the standard MacroEnv
for this back end (see Text.RE.TestBench)
preludeTestsFailing :: [MacroID] Source #
the macros in the standard environment that are failing their tests (checked by the test suite to be empty)
preludeTable :: String Source #
a table the standard macros in markdown format
preludeSummary :: PreludeMacro -> String Source #
a summary of the macros in the standard environment for this back end in plain text
preludeSources :: String Source #
a listing of the RE text for each macro in the standard environment with all macros expanded to normal form
preludeSource :: PreludeMacro -> String Source #
the prelude source of a given macro in the standard environment
IsRegex
The IsRegex
class is used to abstract over the different regex back ends and
the text types they work with -- see Text.RE.Tools.IsRegex for details.
module Text.RE.Tools.IsRegex
The IsRegex Instances
These module exports merely provide the IsRegex
instances.