| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Regex.Base
Description
This module exports base types and functions. You can use these to define
 functions to work on arbitrary sequence types. If you want to work with
 Text or String, import and use Regex.Text or Regex.List instead.
Synopsis
- data RE c a
- data Parser c a
- compile :: RE c a -> Parser c a
- compileBounded :: Int -> RE c a -> Maybe (Parser c a)
- data ParserState c a
- prepareParser :: Parser c a -> ParserState c a
- stepParser :: ParserState c a -> c -> Maybe (ParserState c a)
- finishParser :: ParserState c a -> Maybe a
- type Foldr f a = forall b. (a -> b -> b) -> b -> f -> b
- parseFoldr :: Foldr f c -> Parser c a -> f -> Maybe a
- token :: (c -> Maybe a) -> RE c a
- anySingle :: RE c c
- single :: Eq c => c -> RE c c
- satisfy :: (c -> Bool) -> RE c c
- foldlMany :: (b -> a -> b) -> b -> RE c a -> RE c b
- foldlManyMin :: (b -> a -> b) -> b -> RE c a -> RE c b
- data Many a
- manyr :: RE c a -> RE c (Many a)
- optionalMin :: RE c a -> RE c (Maybe a)
- someMin :: RE c a -> RE c [a]
- manyMin :: RE c a -> RE c [a]
- atLeast :: Int -> RE c a -> RE c [a]
- atMost :: Int -> RE c a -> RE c [a]
- betweenCount :: (Int, Int) -> RE c a -> RE c [a]
- atLeastMin :: Int -> RE c a -> RE c [a]
- atMostMin :: Int -> RE c a -> RE c [a]
- betweenCountMin :: (Int, Int) -> RE c a -> RE c [a]
- sepBy :: RE c a -> RE c sep -> RE c [a]
- sepBy1 :: RE c a -> RE c sep -> RE c [a]
- endBy :: RE c a -> RE c sep -> RE c [a]
- endBy1 :: RE c a -> RE c sep -> RE c [a]
- sepEndBy :: RE c a -> RE c sep -> RE c [a]
- sepEndBy1 :: RE c a -> RE c sep -> RE c [a]
- chainl1 :: RE c a -> RE c (a -> a -> a) -> RE c a
- chainr1 :: RE c a -> RE c (a -> a -> a) -> RE c a
- toFind :: RE c a -> RE c a
- toFindMany :: RE c a -> RE c [a]
- fmap' :: (a -> b) -> RE c a -> RE c b
- liftA2' :: (a1 -> a2 -> b) -> RE c a1 -> RE c a2 -> RE c b
- foldlMany' :: (b -> a -> b) -> b -> RE c a -> RE c b
- foldlManyMin' :: (b -> a -> b) -> b -> RE c a -> RE c b
RE and Parser
A regular expression. Operates on a sequence of elements of type c and
 capable of parsing into an a.
A RE is a Functor, Applicative, and Alternative.
- pure: Succeed without consuming input.
- liftA2,- <*>,- *>,- <*: Sequential composition.
- empty: Fail.
- <|>: Alternative composition. Left-biased, i.e. the result of parsing using- a <|> bis the result of parsing using- aif it succeeds, otherwise it is the result of parsing using- bif it succeeds, otherwise parsing fails.
- many: Zero or more.- many aparses multiple- as sequentially. Biased towards matching more. Use- manyMinfor a bias towards matching less. Also see the section "Looping parsers".
- some: One or more.- some aparses multiple- as sequentially. Biased towards matching more. Use- someMinfor a bias towards matching less.
In addition to expected Functor, Applicative, and Alternative laws,
 RE obeys these Applicative-Alternative laws:
a <*> empty = empty empty <*> a = empty (a <|> b) <*> c = (a <*> c) <|> (b <*> c) a <*> (b <|> c) = (a <*> b) <|> (a <*> c)
Note that, because of bias, it is not true that a <|> b = b <|> a.
Performance note: Prefer the smaller of equivalent regexes, i.e. prefer
 (a <|> b) <*> c over (a <*> c) <|> (b <*> c).
Compile
compile :: RE c a -> Parser c a Source #
\(O(m)\). Compile a RE c a to a Parser c a.
Note: compile does not limit the size of the RE. See compileBounded
 if you would like to limit the size.
 REs with size greater than (maxBound::Int) `div` 2 are not supported
 and the behavior of such a RE is undefined.
compileBounded :: Int -> RE c a -> Maybe (Parser c a) Source #
\(O(\min(l,m))\). Compile a RE c a to a Parser c a.
Returns Nothing if the size of the RE is greater than the provided limit
 \(l\). You may want to use this if you suspect that the RE may be too
 large, for instance if the regex is constructed from an untrusted source.
While the exact size of a RE depends on an internal representation, it can
 be assumed to be in the same order as the length of a
 regex pattern
 corresponding to the RE.
Parse
The functions prepareParser, stepParser, and finishParser grant
 a large amount of control over the parsing process, making it possible to
 parse in a resumable or even branching manner.
As a simpler alternative to the trio of functions above, parseFoldr can be
 used on any sequence type that can be folded over.
data ParserState c a Source #
The state maintained for parsing.
prepareParser :: Parser c a -> ParserState c a Source #
\(O(m \log m)\). Prepare a parser for input.
stepParser :: ParserState c a -> c -> Maybe (ParserState c a) Source #
\(O(m \log m)\). Step a parser by feeding a single element c. Returns
 Nothing if the parse has failed regardless of further input. Otherwise,
 returns an updated ParserState.
finishParser :: ParserState c a -> Maybe a Source #
\(O(1)\). Get the parse result for the input fed into the parser so far.
parseFoldr :: Foldr f c -> Parser c a -> f -> Maybe a Source #
\(O(mn \log m)\). Run a parser given a sequence f and a fold of f.
REs and combinators
foldlMany :: (b -> a -> b) -> b -> RE c a -> RE c b Source #
Parse many occurences of the given RE. Biased towards matching more.
Also see the section "Looping parsers".
foldlManyMin :: (b -> a -> b) -> b -> RE c a -> RE c b Source #
Parse many occurences of the given RE. Minimal, i.e. biased towards
 matching less.
Instances
| Foldable Many Source # | |
| Defined in Regex.Internal.Regex Methods fold :: Monoid m => Many m -> m # foldMap :: Monoid m => (a -> m) -> Many a -> m # foldMap' :: Monoid m => (a -> m) -> Many a -> m # foldr :: (a -> b -> b) -> b -> Many a -> b # foldr' :: (a -> b -> b) -> b -> Many a -> b # foldl :: (b -> a -> b) -> b -> Many a -> b # foldl' :: (b -> a -> b) -> b -> Many a -> b # foldr1 :: (a -> a -> a) -> Many a -> a # foldl1 :: (a -> a -> a) -> Many a -> a # elem :: Eq a => a -> Many a -> Bool # maximum :: Ord a => Many a -> a # | |
| Eq1 Many Source # | |
| Ord1 Many Source # | |
| Defined in Regex.Internal.Regex | |
| Show1 Many Source # | |
| Functor Many Source # | |
| NFData1 Many Source # | |
| Defined in Regex.Internal.Regex | |
| Show a => Show (Many a) Source # | |
| NFData a => NFData (Many a) Source # | |
| Defined in Regex.Internal.Regex | |
| Eq a => Eq (Many a) Source # | |
| Ord a => Ord (Many a) Source # | |
manyr :: RE c a -> RE c (Many a) Source #
Zero or more. Biased towards matching more.
Also see the section "Looping parsers".
optionalMin :: RE c a -> RE c (Maybe a) Source #
Zero or one. Minimal, i.e. biased towards zero.
Use Control.Applicative. for the same but biased towards one.optional
betweenCount :: (Int, Int) -> RE c a -> RE c [a] Source #
Between m and n times (inclusive). Biased towards matching more.
atLeastMin :: Int -> RE c a -> RE c [a] Source #
At least n times. Minimal, i.e. biased towards matching less.
atMostMin :: Int -> RE c a -> RE c [a] Source #
At most n times. Minimal, i.e. biased towards matching less.
betweenCountMin :: (Int, Int) -> RE c a -> RE c [a] Source #
Between m and n times (inclusive). Minimal, i.e. biased towards matching less.
sepBy :: RE c a -> RE c sep -> RE c [a] Source #
r `sepBy` sep parses zero or more occurences of r, separated by
 sep. Biased towards matching more.
sepBy1 :: RE c a -> RE c sep -> RE c [a] Source #
r `sepBy1` sep parses one or more occurences of r, separated by
 sep. Biased towards matching more.
endBy :: RE c a -> RE c sep -> RE c [a] Source #
r `endBy` sep parses zero or more occurences of r, separated and
 ended by sep. Biased towards matching more.
endBy1 :: RE c a -> RE c sep -> RE c [a] Source #
r `endBy1` sep parses one or more occurences of r, separated and
 ended by sep. Biased towards matching more.
sepEndBy :: RE c a -> RE c sep -> RE c [a] Source #
r `sepEndBy` sep parses zero or more occurences of r, separated and
 optionally ended by sep. Biased towards matching more.
sepEndBy1 :: RE c a -> RE c sep -> RE c [a] Source #
r `sepEndBy1` sep parses one or more occurences of r, separated and
 optionally ended by sep. Biased towards matching more.
chainl1 :: RE c a -> RE c (a -> a -> a) -> RE c a Source #
chainl1 r op parses one or more occurences of r, separated by op.
 The result is obtained by left associative application of all functions
 returned by op to the values returned by p. Biased towards matching more.
chainr1 :: RE c a -> RE c (a -> a -> a) -> RE c a Source #
chainr1 r op parses one or more occurences of r, separated by op.
 The result is obtained by right associative application of all functions
 returned by op to the values returned by p. Biased towards matching more.
toFind :: RE c a -> RE c a Source #
Results in the first occurence of the given RE. Fails if no occurence
 is found.
toFindMany :: RE c a -> RE c [a] Source #
Results in all non-overlapping occurences of the given RE. Always
 succeeds.
Strict combinators
These combinators force the result before continuing parsing. But beware!
 If that particular parse ends up failing, the work done will have been for
 nothing. This can blow up the complexity of parsing. For instance,
 fmap' sum (many digit) is \(O(n^2)\).
These functions are intended to be used when the work done in forcing the
 result is guaranteed to be cheaper than creating a thunk, saving memory and
 time.
 For instance, liftA2' (:) is a good usage, since (:) does a small amount
 of work and a thunk is avoided. As another example, liftA2' ((+) @Int) is
 not a good usage, because (+) is strict and forces its arguments,
 performing an arbitrary amount of work. However, it is okay to use
 liftA2' ((+) @Int) if it is known for certain that its arguments will be
 in WHNF.
WARNING: If you are not sure whether to use these function,
 don't use these functions. Simply use fmap, liftA2, foldlMany or
 foldlManyMin instead.
foldlMany' :: (b -> a -> b) -> b -> RE c a -> RE c b Source #
foldlManyMin' :: (b -> a -> b) -> b -> RE c a -> RE c b Source #