regex-applicative-0.3.0.2: Regex-based parsing with applicative interface

Stabilityexperimental
MaintainerRoman Cheplyaka <roma@ro-che.info>
Safe HaskellSafe-Inferred

Text.Regex.Applicative

Description

To get started, see some examples on the wiki: https://github.com/feuerbach/regex-applicative/wiki/Examples

Synopsis

Documentation

data RE s a Source

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 iff ra matches, and its return value is the result of applying f to the return value of ra.
  • pure x matches the empty string (i.e. it does not consume any symbols), and its return value is x
  • rf <*> ra matches a string iff it is a concatenation of two strings: one matched by rf and the other matched by ra. The return value is f a, where f and a are the return values of rf and ra respectively.
  • ra <|> rb matches a string which is accepted by either ra or rb. It is left-biased, so if both can match, the result of ra is used.
  • empty is a regular expression which does not match any string.
  • many ra matches concatenation of zero or more strings matched by ra and returns the list of ra's return values on those strings.
  • some ra matches concatenation of one or more strings matched by ra and returns the list of ra's return values on those strings.

Instances

Functor (RE s) 
Applicative (RE s) 
Alternative (RE s) 
(~ * char Char, ~ * string String) => IsString (RE char string) 

sym :: Eq s => s -> RE s sSource

Match and return the given symbol

psym :: (s -> Bool) -> RE s sSource

Match and return a single symbol which satisfies the predicate

anySym :: RE s sSource

Match and return any single 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 bSource

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.

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","")

withMatched :: RE s a -> RE s (a, [s])Source

Return matched symbols as part of the return value

match :: RE s a -> [s] -> Maybe aSource

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

(=~) :: [s] -> RE s a -> Maybe aSource

s =~ a = match a s

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.