Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.RE.TDFA.ByteString.Lazy
Contents
- (*=~) :: ByteString -> RE -> Matches ByteString
- (?=~) :: ByteString -> RE -> Match ByteString
- (*=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString
- (?=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString
- (=~) :: (Typeable a, RegexContext Regex ByteString a, RegexMaker Regex CompOption ExecOption String) => ByteString -> RE -> a
- (=~~) :: (Monad m, Functor m, Typeable a, RegexContext Regex ByteString a, RegexMaker Regex CompOption ExecOption String) => ByteString -> RE -> m a
- 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
- data SimpleREOptions
- reSource :: RE -> String
- compileRegex :: (Functor m, Monad m) => String -> m RE
- compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> String -> m RE
- escape :: (Functor m, Monad m) => (String -> String) -> String -> m RE
- escapeWith :: (Functor m, Monad m) => SimpleREOptions -> (String -> String) -> String -> m RE
- escapeREString :: String -> String
- module Text.RE.ZeInternals.TDFA
- ed :: QuasiQuoter
- edMS :: QuasiQuoter
- edMI :: QuasiQuoter
- edBS :: QuasiQuoter
- edBI :: QuasiQuoter
- edMultilineSensitive :: QuasiQuoter
- edMultilineInsensitive :: QuasiQuoter
- edBlockSensitive :: QuasiQuoter
- edBlockInsensitive :: QuasiQuoter
- ed_ :: QuasiQuoter
Tutorial
We have a regex tutorial at http://tutorial.regex.uk.
The Matches
and Match
Operators
(*=~) :: ByteString -> RE -> Matches ByteString Source #
find all matches in text; e.g., to count the number of naturals in s:
countMatches $ s *=~ [re|[0-9]+|]
(?=~) :: ByteString -> RE -> Match ByteString Source #
find first match in text
The SearchReplace
Operators
(*=~/) :: ByteString -> SearchReplace RE ByteString -> ByteString Source #
search and replace all occurrences; e.g., this section will yield a function to convert every a YYYY-MM-DD into a DDMMYYYY:
(*=~ [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
The Classic rexex-base match Operators
(=~) :: (Typeable a, RegexContext Regex ByteString a, RegexMaker Regex CompOption ExecOption String) => ByteString -> RE -> a Source #
the regex-base polymorphic match operator
(=~~) :: (Monad m, Functor m, Typeable a, RegexContext Regex ByteString a, RegexMaker Regex CompOption ExecOption String) => ByteString -> RE -> m a Source #
the regex-base monadic, polymorphic match operator
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
The RE
Type and Functions
the RE type for this back end representing a well-formed, compiled RE
Instances
data SimpleREOptions Source #
the default API uses these simple, universal RE options,
which get auto-converted into the apropriate 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
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 |
compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> String -> m RE Source #
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
escapeREString :: String -> String Source #
Convert a string into a regular expression that will amtch that string
module Text.RE.ZeInternals.TDFA
ed :: 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
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
ed_ :: QuasiQuoter Source #
the [ed| ... /// ... |]
quasi quoters