uu-parsinglib-2.5.4.1: Online, error-correcting parser combinators; monadic and applicative interfaces

Text.ParserCombinators.UU.Derived

Contents

Synopsis

Some common combinators for oft occurring constructs

pReturn :: a -> P str aSource

pReturn is defined for upwards comptaibility

pFail :: P str aSource

pFail is defined for upwards comptaibility, and is the unit for |

opt :: P st a -> a -> P st aSource

Optionally recognize parser p.

If p can be recognized, the return value of p is used. Otherwise, the value v is used. Note that opt is greedy, if you do not want this use ... | pure v instead. Furthermore, p should not recognise the empty string, since this would make your parser ambiguous!!

pMaybe :: P st a -> P st (Maybe a)Source

pMaybe greedily recognises its argument. If not Nothing is returned.

pEither :: P str a -> P str b -> P str (Either a b)Source

pEither recognises either one of its arguments.

(<$$>) :: (a -> b -> c) -> P st b -> P st (a -> c)Source

$$ is the version of $ which maps on its second argument

(<??>) :: P st a -> P st (a -> a) -> P st aSource

?? parses an optional postfix element and applies its result to its left hand result

pPacked :: P st b1 -> P st b2 -> P st a -> P st aSource

pPackes surrounds its third parser with the first and the seond one, keeping only the middle result

The collection of iterating combinators, all in a greedy (default) and a non-greedy variant

pFoldr :: (a -> a1 -> a1, a1) -> P st a -> P st a1Source

pFoldr_ng :: (a -> a1 -> a1, a1) -> P st a -> P st a1Source

pFoldr1 :: (v -> b -> b, b) -> P st v -> P st bSource

pFoldr1_ng :: (v -> b -> b, b) -> P st v -> P st bSource

pFoldrSep :: (v -> b -> b, b) -> P st a -> P st v -> P st bSource

pFoldrSep_ng :: (v -> b -> b, b) -> P st a -> P st v -> P st bSource

pFoldr1Sep :: (a -> b -> b, b) -> P st a1 -> P st a -> P st bSource

pFoldr1Sep_ng :: (a -> b -> b, b) -> P st a1 -> P st a -> P st bSource

list_alg :: (a -> [a] -> [a], [a1])Source

pList :: P st a -> P st [a]Source

pList_ng :: P st a -> P st [a]Source

pList1 :: P st a -> P st [a]Source

pList1_ng :: P st a -> P st [a]Source

pListSep :: P st a1 -> P st a -> P st [a]Source

pListSep_ng :: P st a1 -> P st a -> P st [a]Source

pList1Sep :: P st a1 -> P st a -> P st [a]Source

pList1Sep_ng :: P st a1 -> P st a -> P st [a]Source

pChainr :: P st (c -> c -> c) -> P st c -> P st cSource

pChainr_ng :: P st (c -> c -> c) -> P st c -> P st cSource

pChainl :: P st (c -> c -> c) -> P st c -> P st cSource

pChainl_ng :: P st (c -> c -> c) -> P st c -> P st cSource

pAny :: (a -> P st a1) -> [a] -> P st a1Source

Build a parser for each elemnt in its argument list and tries them all.

pAnySym :: Provides st s s => [s] -> P st sSource

Parses any of the symbols in l.

Merging parsers

data Freq p Source

Constructors

AtLeast Int p 
AtMost Int p 
Between Int Int p 
One p 
Many p 
Opt p 
Never p 

Instances

split :: [Freq p] -> ([Freq p] -> [Freq p]) -> [(p, [Freq p])]Source

toParser :: [Freq (P st (d -> d))] -> P st d -> P st dSource

newtype MergeSpec p Source

Constructors

MergeSpec p 

(<||>) :: MergeSpec (c, [Freq (P st (d -> d))], e -> f -> g) -> MergeSpec (h, [Freq (P st (i -> i))], g -> j -> k) -> MergeSpec ((c, h), [Freq (P st ((d, i) -> (d, i)))], e -> (f, j) -> k)Source

pMerge :: c -> MergeSpec (d, [Freq (P st (d -> d))], c -> d -> e) -> P st eSource

pMergeSep :: (c, P st a) -> MergeSpec (d, [Freq (P st (d -> d))], c -> d -> e) -> P st eSource