Copyright | (c) Roman Cheplyaka |
---|---|
License | MIT |
Maintainer | Roman Cheplyaka <roma@ro-che.info> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
To get started, see some examples on the wiki: https://github.com/feuerbach/regex-applicative/wiki/Examples
- data RE s a
- sym :: Eq s => s -> RE s s
- psym :: (s -> Bool) -> RE s s
- msym :: (s -> Maybe a) -> RE s a
- anySym :: RE s s
- string :: Eq a => [a] -> RE a [a]
- reFoldl :: Greediness -> (b -> a -> b) -> b -> RE s a -> RE s b
- data Greediness
- few :: RE s a -> RE s [a]
- comap :: (s2 -> s1) -> RE s1 a -> RE s2 a
- withMatched :: RE s a -> RE s (a, [s])
- match :: RE s a -> [s] -> Maybe a
- (=~) :: [s] -> RE s a -> Maybe a
- replace :: RE s [s] -> [s] -> [s]
- findFirstPrefix :: RE s a -> [s] -> Maybe (a, [s])
- findLongestPrefix :: RE s a -> [s] -> Maybe (a, [s])
- findShortestPrefix :: RE s a -> [s] -> Maybe (a, [s])
- findFirstInfix :: RE s a -> [s] -> Maybe ([s], a, [s])
- findLongestInfix :: RE s a -> [s] -> Maybe ([s], a, [s])
- findShortestInfix :: RE s a -> [s] -> Maybe ([s], a, [s])
- module Control.Applicative
Documentation
Type of regular expressions that recognize symbols of type s
and
produce a result of type a
.
Regular expressions can be built using Functor
, Applicative
and
Alternative
instances in the following natural way:
f
<$>
ra
matches iffra
matches, and its return value is the result of applyingf
to the return value ofra
.pure
x
matches the empty string (i.e. it does not consume any symbols), and its return value isx
rf
<*>
ra
matches a string iff it is a concatenation of two strings: one matched byrf
and the other matched byra
. The return value isf a
, wheref
anda
are the return values ofrf
andra
respectively.ra
<|>
rb
matches a string which is accepted by eitherra
orrb
. It is left-biased, so if both can match, the result ofra
is used.empty
is a regular expression which does not match any string.many
ra
matches concatenation of zero or more strings matched byra
and returns the list ofra
's return values on those strings.some
ra
matches concatenation of one or more strings matched byra
and returns the list ofra
's return values on those strings.
psym :: (s -> Bool) -> RE s s Source #
Match and return a single symbol which satisfies the predicate
msym :: (s -> Maybe a) -> RE s a Source #
Like psym
, but allows to return a computed value instead of the
original symbol
string :: Eq a => [a] -> RE a [a] Source #
Match and return the given sequence of symbols.
Note that there is an IsString
instance for regular expression, so
if you enable the OverloadedStrings
language extension, you can write
string "foo"
simply as "foo"
.
Example:
{-# LANGUAGE OverloadedStrings #-} import Text.Regex.Applicative number = "one" *> pure 1 <|> "two" *> pure 2 main = print $ "two" =~ number
reFoldl :: Greediness -> (b -> a -> b) -> b -> RE s a -> RE s b Source #
Match zero or more instances of the given expression, which are combined using the given folding function.
Greediness
argument controls whether this regular expression should match
as many as possible (Greedy
) or as few as possible (NonGreedy
) instances
of the underlying expression.
data Greediness Source #
few :: RE s a -> RE s [a] Source #
Match zero or more instances of the given expression, but as
few of them as possible (i.e. non-greedily). A greedy equivalent of few
is many
.
Examples:
Text.Regex.Applicative> findFirstPrefix (few anySym <* "b") "ababab" Just ("a","abab") Text.Regex.Applicative> findFirstPrefix (many anySym <* "b") "ababab" Just ("ababa","")
comap :: (s2 -> s1) -> RE s1 a -> RE s2 a Source #
RE
is a profunctor. This is its contravariant map.
(A dependency on the profunctors
package doesn't seem justified.)
withMatched :: RE s a -> RE s (a, [s]) Source #
Return matched symbols as part of the return value
match :: RE s a -> [s] -> Maybe a Source #
Attempt to match a string of symbols against the regular expression. Note that the whole string (not just some part of it) should be matched.
Examples:
Text.Regex.Applicative> match (sym 'a' <|> sym 'b') "a" Just 'a' Text.Regex.Applicative> match (sym 'a' <|> sym 'b') "ab" Nothing
replace :: RE s [s] -> [s] -> [s] Source #
Replace matches of the regular expression with its value.
Text.Regex.Applicative > replace ("!" <$ sym 'f' <* some (sym 'o')) "quuxfoofooooofoobarfobar" "quux!!!bar!bar"
findFirstPrefix :: RE s a -> [s] -> Maybe (a, [s]) Source #
Find a string prefix which is matched by the regular expression.
Of all matching prefixes, pick one using left bias (prefer the left part of
<|>
to the right part) and greediness.
This is the match which a backtracking engine (such as Perl's one) would find first.
If match is found, the rest of the input is also returned.
Examples:
Text.Regex.Applicative> findFirstPrefix ("a" <|> "ab") "abc" Just ("a","bc") Text.Regex.Applicative> findFirstPrefix ("ab" <|> "a") "abc" Just ("ab","c") Text.Regex.Applicative> findFirstPrefix "bc" "abc" Nothing
findLongestPrefix :: RE s a -> [s] -> Maybe (a, [s]) Source #
Find the longest string prefix which is matched by the regular expression.
Submatches are still determined using left bias and greediness, so this is different from POSIX semantics.
If match is found, the rest of the input is also returned.
Examples:
Text.Regex.Applicative Data.Char> let keyword = "if" Text.Regex.Applicative Data.Char> let identifier = many $ psym isAlpha Text.Regex.Applicative Data.Char> let lexeme = (Left <$> keyword) <|> (Right <$> identifier) Text.Regex.Applicative Data.Char> findLongestPrefix lexeme "if foo" Just (Left "if"," foo") Text.Regex.Applicative Data.Char> findLongestPrefix lexeme "iffoo" Just (Right "iffoo","")
findShortestPrefix :: RE s a -> [s] -> Maybe (a, [s]) Source #
Find the shortest prefix (analogous to findLongestPrefix
)
findFirstInfix :: RE s a -> [s] -> Maybe ([s], a, [s]) Source #
Find the leftmost substring that is matched by the regular expression.
Otherwise behaves like findFirstPrefix
. Returns the result together with
the prefix and suffix of the string surrounding the match.
findLongestInfix :: RE s a -> [s] -> Maybe ([s], a, [s]) Source #
Find the leftmost substring that is matched by the regular expression.
Otherwise behaves like findLongestPrefix
. Returns the result together with
the prefix and suffix of the string surrounding the match.
findShortestInfix :: RE s a -> [s] -> Maybe ([s], a, [s]) Source #
Find the leftmost substring that is matched by the regular expression.
Otherwise behaves like findShortestPrefix
. Returns the result together with
the prefix and suffix of the string surrounding the match.
module Control.Applicative