parser-regex-0.2.0.1: Regex based parsers
Safe HaskellSafe-Inferred
LanguageHaskell2010

Regex.Internal.Regex

Description

This is an internal module. You probably don't need to import this.

Synopsis

Documentation

data RE c a where Source #

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 <|> b is the result of parsing using a if it succeeds, otherwise it is the result of parsing using b if it succeeds, otherwise parsing fails.
  • many: Zero or more. many a parses multiple as sequentially. Biased towards matching more. Use manyMin for a bias towards matching less. Also see the section "Looping parsers".
  • some: One or more. some a parses multiple as sequentially. Biased towards matching more. Use someMin 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).

Constructors

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 

Instances

Instances details
Alternative (RE c) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

empty :: RE c a #

(<|>) :: RE c a -> RE c a -> RE c a #

some :: RE c a -> RE c [a] #

many :: RE c a -> RE c [a] #

Applicative (RE c) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

pure :: a -> RE c a #

(<*>) :: RE c (a -> b) -> RE c a -> RE c b #

liftA2 :: (a -> b -> c0) -> RE c a -> RE c b -> RE c c0 #

(*>) :: RE c a -> RE c b -> RE c b #

(<*) :: RE c a -> RE c b -> RE c a #

Functor (RE c) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

fmap :: (a -> b) -> RE c a -> RE c b #

(<$) :: a -> RE c b -> RE c a #

Monoid a => Monoid (RE c a) Source #

mempty = pure mempty

Instance details

Defined in Regex.Internal.Regex

Methods

mempty :: RE c a #

mappend :: RE c a -> RE c a -> RE c a #

mconcat :: [RE c a] -> RE c a #

Semigroup a => Semigroup (RE c a) Source #

(<>) = liftA2 (<>)

Instance details

Defined in Regex.Internal.Regex

Methods

(<>) :: RE c a -> RE c a -> RE c a #

sconcat :: NonEmpty (RE c a) -> RE c a #

stimes :: Integral b => b -> RE c a -> RE c a #

data Strictness Source #

Constructors

Strict 
NonStrict 

data Greediness Source #

Constructors

Greedy 
Minimal 

data Many a Source #

A repeating value or a finite list.

Constructors

Repeat a

A single value repeating indefinitely

Finite [a]

A finite list

Instances

Instances details
Eq1 Many Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

liftEq :: (a -> b -> Bool) -> Many a -> Many b -> Bool #

Ord1 Many Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

liftCompare :: (a -> b -> Ordering) -> Many a -> Many b -> Ordering #

Show1 Many Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Many a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Many a] -> ShowS #

NFData1 Many Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

liftRnf :: (a -> ()) -> Many a -> () #

Functor Many Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

fmap :: (a -> b) -> Many a -> Many b #

(<$) :: a -> Many b -> Many a #

Foldable Many Source # 
Instance details

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 #

toList :: Many a -> [a] #

null :: Many a -> Bool #

length :: Many a -> Int #

elem :: Eq a => a -> Many a -> Bool #

maximum :: Ord a => Many a -> a #

minimum :: Ord a => Many a -> a #

sum :: Num a => Many a -> a #

product :: Num a => Many a -> a #

NFData a => NFData (Many a) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

rnf :: Many a -> () #

Show a => Show (Many a) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

showsPrec :: Int -> Many a -> ShowS #

show :: Many a -> String #

showList :: [Many a] -> ShowS #

Eq a => Eq (Many a) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

(==) :: Many a -> Many a -> Bool #

(/=) :: Many a -> Many a -> Bool #

Ord a => Ord (Many a) Source # 
Instance details

Defined in Regex.Internal.Regex

Methods

compare :: Many a -> Many a -> Ordering #

(<) :: Many a -> Many a -> Bool #

(<=) :: Many a -> Many a -> Bool #

(>) :: Many a -> Many a -> Bool #

(>=) :: Many a -> Many a -> Bool #

max :: Many a -> Many a -> Many a #

min :: Many a -> Many a -> Many a #

token :: (c -> Maybe a) -> RE c a Source #

Parse a c into an a if the given function returns Just.

anySingle :: RE c c Source #

Parse any c.

single :: Eq c => c -> RE c c Source #

Parse the given c.

satisfy :: (c -> Bool) -> RE c c Source #

Parse a c if it satisfies the given predicate.

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.optional for the same but biased towards one.

someMin :: RE c a -> RE c [a] Source #

One or more. Minimal, i.e. biased towards matching less.

manyMin :: RE c a -> RE c [a] Source #

Zero or more. Minimal, i.e. biased towards matching less.

atLeast :: Int -> RE c a -> RE c [a] Source #

At least n times. Biased towards matching more.

atMost :: Int -> RE c a -> RE c [a] Source #

At most n times. Biased towards matching more.

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.

fmap' :: (a -> b) -> RE c a -> RE c b Source #

liftA2' :: (a1 -> a2 -> b) -> RE c a1 -> RE c a2 -> RE c b Source #

foldlMany' :: (b -> a -> b) -> b -> RE c a -> RE c b Source #

foldlManyMin' :: (b -> a -> b) -> b -> RE c a -> RE c b Source #