Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This is an internal module. You probably don't need to import this.
Synopsis
- data RE c a where
- RToken :: forall c a. !(c -> Maybe a) -> RE c a
- RFmap :: forall a1 a c. !Strictness -> !(a1 -> a) -> !(RE c a1) -> RE c a
- RFmap_ :: forall a c a1. a -> !(RE c a1) -> RE c a
- RPure :: forall a c. a -> RE c a
- RLiftA2 :: forall a1 a2 a c. !Strictness -> !(a1 -> a2 -> a) -> !(RE c a1) -> !(RE c a2) -> RE c a
- REmpty :: forall c a. RE c a
- RAlt :: forall c a. !(RE c a) -> !(RE c a) -> RE c a
- RFold :: forall a a1 c. !Strictness -> !Greediness -> !(a -> a1 -> a) -> a -> !(RE c a1) -> RE c a
- RMany :: forall a1 a a2 c. !(a1 -> a) -> !(a2 -> a) -> !(a2 -> a1 -> a2) -> !a2 -> !(RE c a1) -> RE c a
- data Strictness
- data Greediness
- data Many 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
- 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
Documentation
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 usinga <|> b
is the result of parsing usinga
if it succeeds, otherwise it is the result of parsing usingb
if it succeeds, otherwise parsing fails.many
: Zero or more.many a
parses multiplea
s sequentially. Biased towards matching more. UsemanyMin
for a bias towards matching less. Also see the section "Looping parsers".some
: One or more.some a
parses multiplea
s sequentially. Biased towards matching more. UsesomeMin
for 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 tip: Prefer the smaller of equivalent regexes, i.e. prefer
(a <|> b) <*> c
over (a <*> c) <|> (b <*> c)
.
RToken :: forall c a. !(c -> Maybe a) -> RE c a | |
RFmap :: forall a1 a c. !Strictness -> !(a1 -> a) -> !(RE c a1) -> RE c a | |
RFmap_ :: forall a c a1. a -> !(RE c a1) -> RE c a | |
RPure :: forall a c. a -> RE c a | |
RLiftA2 :: forall a1 a2 a c. !Strictness -> !(a1 -> a2 -> a) -> !(RE c a1) -> !(RE c a2) -> RE c a | |
REmpty :: forall c a. RE c a | |
RAlt :: forall c a. !(RE c a) -> !(RE c a) -> RE c a | |
RFold :: forall a a1 c. !Strictness -> !Greediness -> !(a -> a1 -> a) -> a -> !(RE c a1) -> RE c a | |
RMany :: forall a1 a a2 c. !(a1 -> a) -> !(a2 -> a) -> !(a2 -> a1 -> a2) -> !a2 -> !(RE c a1) -> RE c a |
data Strictness Source #
data Greediness Source #
A repeating value or a finite list.
Instances
Eq1 Many Source # | |
Ord1 Many Source # | |
Defined in Regex.Internal.Regex | |
Show1 Many Source # | |
NFData1 Many Source # | |
Defined in Regex.Internal.Regex | |
Functor Many Source # | |
Foldable Many Source # | |
Defined in Regex.Internal.Regex 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 # | |
NFData a => NFData (Many a) Source # | |
Defined in Regex.Internal.Regex | |
Show a => Show (Many a) Source # | |
Eq a => Eq (Many a) Source # | |
Ord a => Ord (Many a) Source # | |
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.
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.
foldlMany' :: (b -> a -> b) -> b -> RE c a -> RE c b Source #
foldlManyMin' :: (b -> a -> b) -> b -> RE c a -> RE c b Source #