Copyright | (C) 2016-17 Chris Dornan |
---|---|
License | BSD3 (see the LICENSE file) |
Maintainer | Chris Dornan <chris.dornan@irisconnect.com> |
Stability | RFC |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Text.RE
Contents
Description
- 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
- class Replace s => IsRegex re s where
- searchReplaceAll :: IsRegex re s => SearchReplace re s -> s -> s
- searchReplaceFirst :: IsRegex re s => SearchReplace re s -> s -> s
- module Text.RE.TDFA
The Tutorial
We have a regex tutorial at http://tutorial.regex.uk.
How to use this library
This module just provides a brief overview of the regex package. You will need to import one of the API modules of which there is a choice which will depend upon two factors:
- Which flavour of regular expression do you want to use? If you need Posix flavour REs then you will want the TDFA modules, otherwise its PCRE for Perl-style REs.
- What type of text do you want to match: (slow)
String
s,ByteString
,ByteString.Lazy
,Text
,Text.Lazy
or the anachronisticSeq Char
or indeed some good old-fashioned polymorphic operators?
While we aim to provide all combinations of these choices, some of them are currently not available. In the regex package we have:
- Text.RE.TDFA.ByteString
- Text.RE.TDFA.ByteString.Lazy
- Text.RE.ZeInternals.TDFA
- Text.RE.TDFA.Sequence
- Text.RE.TDFA.String
- Text.RE.TDFA.Text
- Text.RE.TDFA.Text.Lazy
- Text.RE.TDFA
The PCRE modules are contained in the separate regex-with-pcre
package:
- Text.RE.PCRE.ByteString
- Text.RE.PCRE.ByteString.Lazy
- Text.RE.ZeInternals.PCRE
- Text.RE.PCRE.Sequence
- Text.RE.PCRE.String
- Text.RE.PCRE
Further Use
For more specialist applications we have the following:
- Text.RE.REOptions for specifying back-end specific options;
- Text.RE.Replace for the full replace toolkit;
- Text.RE.TestBench for building up, testing and doumenting; macro environments for use in REs;
- Text.RE.Tools for an AWK-like text-processing toolkit.
The regex Foundational Types
Matches
the result type to use when every match is needed, not just the first match of the RE against the source
Instances
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))
Instances
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
IsRegex
Class IsRegex re t
provides methods for matching the t
type for
the re
back end as well as compiling REs from t
to re
and
getting the source t
back again. The Replace
superclass of
IsRegex
contains a useful toolkit for converting between t
and
String
abd Text
.
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
Minimal complete definition
matchOnce, matchMany, makeRegexWith, makeSearchReplaceWith, regexSource
Methods
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
searchReplaceAll :: IsRegex re s => SearchReplace re s -> s -> s Source #
search and replace all matches in the argument text; e.g., this function will convert every YYYY-MM-DD format date in its argument text into a DD/MM/YYYY date:
searchReplaceAll [ed|${y}([0-9]{4})-0*${m}([0-9]{2})-0*${d}([0-9]{2})///${d}/${m}/${y}|]
searchReplaceFirst :: IsRegex re s => SearchReplace re s -> s -> s 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
:
searchReplaceFirst [ed|[0-9A-Fa-f]{4}///0x$0|]
IsRegex Instances
This module import just imports the IsRegex TDFA s
instances.
module Text.RE.TDFA