| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.RE.TDFA.ByteString
Synopsis
- (*=~) :: ByteString -> RE -> Matches ByteString
- (?=~) :: ByteString -> RE -> Match ByteString
- (*=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString
- (?=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString
- 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
- reSource :: RE -> String
- data SimpleREOptions
- 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
- 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)
- 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
- escapeREString :: String -> String
- (=~) :: (Typeable a, RegexContext Regex ByteString a) => ByteString -> RE -> a
- (=~~) :: (Monad m, MonadFail m, Functor m, Typeable a, RegexContext Regex ByteString a) => ByteString -> RE -> m a
- re :: QuasiQuoter
- reMultilineSensitive :: QuasiQuoter
- reMultilineInsensitive :: QuasiQuoter
- reBlockSensitive :: QuasiQuoter
- reBlockInsensitive :: QuasiQuoter
- reMS :: QuasiQuoter
- reMI :: QuasiQuoter
- reBS :: QuasiQuoter
- reBI :: QuasiQuoter
- re_ :: QuasiQuoter
- edMultilineSensitive :: QuasiQuoter
- edMultilineInsensitive :: QuasiQuoter
- edBlockSensitive :: QuasiQuoter
- edBlockInsensitive :: QuasiQuoter
- ed :: QuasiQuoter
- edMS :: QuasiQuoter
- edMI :: QuasiQuoter
- edBS :: QuasiQuoter
- edBI :: QuasiQuoter
- ed_ :: QuasiQuoter
- cp :: QuasiQuoter
- module Text.RE.Tools.IsRegex
Tutorial
We have a regex tutorial at http://tutorial.regex.uk.
The Matches and Match Operators
(*=~) :: ByteString -> RE -> Matches ByteString Source #
find all the matches in the argument text; e.g., to count the number of naturals in s:
countMatches $ s *=~ [re|[0-9]+|]
(?=~) :: ByteString -> RE -> Match ByteString 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
(*=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString 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}|])(?=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString 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 input text,
 if any, with 0x:
(?=~/ [ed|[0-9A-Fa-f]{4}///0x$0|])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
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_
Constructors
| 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
Compiling and Escaping REs
data SearchReplace re s Source #
contains a compiled RE and replacement template
Constructors
| SearchReplace | |
| Fields 
 | |
Instances
| Functor (SearchReplace re) Source # | |
| Defined in Text.RE.ZeInternals.Types.SearchReplace Methods 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 Methods 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 #
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
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
escapeREString :: String -> String Source #
Convert a string into a regular expression that will match that string
The Classic regex-base Match Operators
(=~) :: (Typeable a, RegexContext Regex ByteString a) => ByteString -> RE -> a Source #
the `regex-base` polymorphic match operator
(=~~) :: (Monad m, MonadFail m, Functor m, Typeable a, RegexContext Regex ByteString a) => ByteString -> 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 [ed|.*///foo|] quasi quoters, with variants for specifying different
 options to the RE compiler (see Text.RE.REOptions).
edMultilineSensitive :: QuasiQuoter Source #
[edMultilineSensitive| ... /// ... |] compiles a case-sensitive, multi-line SearchReplace template
edMultilineInsensitive :: QuasiQuoter Source #
[edMultilineInsensitive| ... /// ... |] compiles a case-insensitive, multi-line SearchReplace template
edBlockSensitive :: QuasiQuoter Source #
[edBlockSensitive| ... /// ... |] compiles a case-sensitive, non-multi-line SearchReplace template
edBlockInsensitive :: QuasiQuoter Source #
[edBlockInsensitive| ... /// ... |] compiles a case-insensitive, non-multi-line SearchReplace template
ed :: QuasiQuoter Source #
[ed| ... /// ... |], is equivalent to [edMultilineSensitive| ... /// ... |],
 compiling a case-sensitive, multi-line SearchReplace
edMS :: QuasiQuoter Source #
[edMS| ... /// ... |] is a shorthand for [edMultilineSensitive| ... /// ... |]
edMI :: QuasiQuoter Source #
[edMI| ... /// ... |] is a shorthand for [edMultilineInsensitive| ... /// ... |]
edBS :: QuasiQuoter Source #
[edBS| ... /// ... |] is a shorthand for [edBlockSensitive| ... /// ... |]
edBI :: QuasiQuoter Source #
[edBI| ... /// ... |] is a shorthand for [edBlockInsensitive| ... /// ... |]
ed_ :: QuasiQuoter Source #
[ed_| ... /// ... |] compiles a SearchReplace template to produce a function that
 takes the RE options (e.g., a SimpleREOptions value) and yields the
 SearchReplace template compiled with those options. For example,
s *=~/ [ed_|${hex}([0-9a-f]+)///0x${hex}|] MultilineInsensitiveprefixes the hexadecimal digit strings in s with 0x, allowing for
 upper- or lower-case hex digits (which is entirely equivalent
 in this example to just using [edMultilineInsensitive|[0-9a-f]+|]).
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}( ... ) ... |].
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
Orphan instances
| IsRegex RE ByteString Source # | |
| Methods matchOnce :: RE -> ByteString -> Match ByteString Source # matchMany :: RE -> ByteString -> Matches ByteString Source # makeRegex :: (Functor m, Monad m, MonadFail m) => ByteString -> m RE Source # makeRegexWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> ByteString -> m RE Source # makeSearchReplace :: (Functor m, Monad m, MonadFail m, IsRegex RE ByteString) => ByteString -> ByteString -> m (SearchReplace RE ByteString) Source # makeSearchReplaceWith :: (Functor m, Monad m, MonadFail m, IsRegex RE ByteString) => SimpleREOptions -> ByteString -> ByteString -> m (SearchReplace RE ByteString) Source # makeEscaped :: (Functor m, Monad m, MonadFail m) => (ByteString -> ByteString) -> ByteString -> m RE Source # makeEscapedWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> (ByteString -> ByteString) -> ByteString -> m RE Source # regexSource :: RE -> ByteString Source # | |