Safe Haskell | None |
---|---|
Language | Haskell2010 |
- (*=~) :: String -> RE -> Matches String
- (?=~) :: String -> RE -> Match String
- (*=~/) :: String -> SearchReplace RE String -> String
- (?=~/) :: String -> SearchReplace RE String -> String
- 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
- data RE
- reSource :: RE -> String
- data SimpleREOptions
- data SearchReplace re s = SearchReplace {
- getSearch :: !re
- getTemplate :: !s
- compileRegex :: (Functor m, Monad m) => String -> m RE
- compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> 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)
- escape :: (Functor m, Monad m) => (String -> String) -> String -> m RE
- escapeWith :: (Functor m, Monad m) => SimpleREOptions -> (String -> String) -> String -> m RE
- escapeREString :: String -> String
- (=~) :: (Typeable a, RegexContext Regex String a, RegexMaker Regex CompOption ExecOption String) => String -> RE -> a
- (=~~) :: (Monad m, Functor m, Typeable a, RegexContext Regex String a, RegexMaker Regex CompOption ExecOption String) => String -> RE -> m a
- class Replace s => IsRegex re s where
- module Text.RE.ZeInternals.TDFA
- module Text.RE.ZeInternals.SearchReplace.TDFA.String
Tutorial
We have a regex tutorial at http://tutorial.regex.uk.
The Matches
and Match
Operators
(*=~) :: String -> RE -> Matches String Source #
find all the matches in the argument text; e.g., to count the number of naturals in s:
countMatches $ s *=~ [re|[0-9]+|]
(?=~) :: String -> RE -> Match String 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
(*=~/) :: String -> SearchReplace RE String -> String 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}|])
(?=~/) :: String -> SearchReplace RE String -> String Source #
search and replace the first occurrence only (if any) in the input text
e.g., to prefix the first string of four hex digits in the imput text,
if any, with 0x
:
(?=~/ [ed|[0-9A-Fa-f]{4}///0x$0|])
Matches
the result type to use when every match is needed, not just the first match of the RE against the source
Functor Matches Source # | |
(RegexContext regex source [MatchText source], RegexLike 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
Match
the result of matching a RE to a text once, listing the text that was matched and the named captures in the RE and all of the substrings matched, with the text captured by the whole RE; a complete failure to match will be represented with an empty array (with bounds (0,-1))
Functor Match Source # | |
(RegexContext regex source (AllTextSubmatches (Array Int) (source, (Int, Int))), RegexLike 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 #
tests whether the RE matched the source text at all
The RE
Type
the RE type for this back end representing a well-formed, compiled 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 [red_| ... /// ... |]
quasi quoters, which generate functions that take an IsOption
option
(e.g., a SimpleReOptions
value) and yields a RE
or SearchReplace
as apropriate. 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 apropriate 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 |
Bounded SimpleREOptions Source # | |
Enum SimpleREOptions Source # | |
Eq SimpleREOptions Source # | |
Ord SimpleREOptions Source # | |
Show SimpleREOptions Source # | |
Lift SimpleREOptions Source # | we need to use this in the quasi quoters to specify |
IsOption SimpleREOptions Source # | |
Compiling and Escaping REs
data SearchReplace re s Source #
contains a compiled RE and replacement template
SearchReplace | |
|
Functor (SearchReplace re) Source # | |
(Show s, Show re) => Show (SearchReplace re s) Source # | |
compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> String -> m RE Source #
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
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; e.g., to compile a RE that will only match the string:
maybe undefined id . escape (("^"++) . (++"$"))
escapeWith :: (Functor m, Monad m) => SimpleREOptions -> (String -> String) -> String -> m RE Source #
a variant of escape
where the SimpleREOptions
are specified
escapeREString :: String -> String Source #
Convert a string into a regular expression that will match that string
The Classic rexex-base Match Operators
(=~) :: (Typeable a, RegexContext Regex String a, RegexMaker Regex CompOption ExecOption String) => String -> RE -> a Source #
the regex-base polymorphic match operator
(=~~) :: (Monad m, Functor m, Typeable a, RegexContext Regex String a, RegexMaker Regex CompOption ExecOption String) => String -> RE -> m a Source #
the regex-base monadic, polymorphic match operator
IsRegex
class Replace s => IsRegex re s where Source #
the IsRegex
class allows polymorhic tools to be written that
will work with a variety of regex back ends and text types
matchOnce :: re -> s -> Match s Source #
finding the first match
matchMany :: re -> s -> Matches s Source #
finding all matches
makeRegex :: (Functor m, Monad m) => s -> m re Source #
compiling an RE, failing if the RE is not well formed
makeRegexWith :: (Functor m, Monad m) => SimpleREOptions -> s -> m re Source #
comiling an RE, specifying the SimpleREOptions
makeSearchReplace :: (Functor m, Monad m, IsRegex re s) => s -> s -> m (SearchReplace re s) Source #
compiling a SearchReplace
template from the RE text and the template Text, failing if they are not well formed
makeSearchReplaceWith :: (Functor m, Monad m, IsRegex re s) => SimpleREOptions -> s -> s -> m (SearchReplace re s) Source #
compiling a SearchReplace
template specifing the SimpleREOptions
for the RE
makeEscaped :: (Functor m, Monad m) => (s -> s) -> s -> m re Source #
incorporate an escaped string into a compiled RE with the default options
makeEscapedWith :: (Functor m, Monad m) => SimpleREOptions -> (s -> s) -> s -> m re Source #
incorporate an escaped string into a compiled RE with the specified SimpleREOptions
regexSource :: re -> s Source #
extract the text of the RE from the RE
The Quasi Quoters and Minor Functions
The [re|.*|]
quasi quoters, with variants for specifing different
options to the RE compiler (see Text.RE.REOptions), and the
specialised back-end types and functions.
module Text.RE.ZeInternals.TDFA
The [ed|.*///foo|]
quasi quoters, with variants for specifing different
options to the RE compiler (see Text.RE.REOptions).