attoparsec-0.13.2.4: Fast combinator parsing for bytestrings and text

CopyrightDaan Leijen 1999-2001 Bryan O'Sullivan 2007-2015
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Data.Attoparsec.Combinator

Contents

Description

Useful parser combinators, similar to those provided by Parsec.

Synopsis

Combinators

try :: Parser i a -> Parser i a Source #

Attempt a parse, and if it fails, rewind the input so that no input appears to have been consumed.

This combinator is provided for compatibility with Parsec. attoparsec parsers always backtrack on failure.

(<?>) infix 0 Source #

Arguments

:: Parser i a 
-> String

the name to use if parsing fails

-> Parser i a 

Name the parser, in case failure occurs.

choice :: Alternative f => [f a] -> f a Source #

choice ps tries to apply the actions in the list ps in order, until one of them succeeds. Returns the value of the succeeding action.

count :: Monad m => Int -> m a -> m [a] Source #

Apply the given action repeatedly, returning every result.

option :: Alternative f => a -> f a -> f a Source #

option x p tries to apply action p. If p fails without consuming input, it returns the value x, otherwise the value returned by p.

priority  = option 0 (digitToInt <$> digit)

many' :: MonadPlus m => m a -> m [a] Source #

many' p applies the action p zero or more times. Returns a list of the returned values of p. The value returned by p is forced to WHNF.

 word  = many' letter

many1 :: Alternative f => f a -> f [a] Source #

many1 p applies the action p one or more times. Returns a list of the returned values of p.

 word  = many1 letter

many1' :: MonadPlus m => m a -> m [a] Source #

many1' p applies the action p one or more times. Returns a list of the returned values of p. The value returned by p is forced to WHNF.

 word  = many1' letter

manyTill :: Alternative f => f a -> f b -> f [a] Source #

manyTill p end applies action p zero or more times until action end succeeds, and returns the list of values returned by p. This can be used to scan comments:

 simpleComment   = string "<!--" *> manyTill anyChar (string "-->")

(Note the overlapping parsers anyChar and string "-->". While this will work, it is not very efficient, as it will cause a lot of backtracking.)

manyTill' :: MonadPlus m => m a -> m b -> m [a] Source #

manyTill' p end applies action p zero or more times until action end succeeds, and returns the list of values returned by p. This can be used to scan comments:

 simpleComment   = string "<!--" *> manyTill' anyChar (string "-->")

(Note the overlapping parsers anyChar and string "-->". While this will work, it is not very efficient, as it will cause a lot of backtracking.)

The value returned by p is forced to WHNF.

sepBy :: Alternative f => f a -> f s -> f [a] Source #

sepBy p sep applies zero or more occurrences of p, separated by sep. Returns a list of the values returned by p.

commaSep p  = p `sepBy` (char ',')

sepBy' :: MonadPlus m => m a -> m s -> m [a] Source #

sepBy' p sep applies zero or more occurrences of p, separated by sep. Returns a list of the values returned by p. The value returned by p is forced to WHNF.

commaSep p  = p `sepBy'` (char ',')

sepBy1 :: Alternative f => f a -> f s -> f [a] Source #

sepBy1 p sep applies one or more occurrences of p, separated by sep. Returns a list of the values returned by p.

commaSep p  = p `sepBy1` (char ',')

sepBy1' :: MonadPlus m => m a -> m s -> m [a] Source #

sepBy1' p sep applies one or more occurrences of p, separated by sep. Returns a list of the values returned by p. The value returned by p is forced to WHNF.

commaSep p  = p `sepBy1'` (char ',')

skipMany :: Alternative f => f a -> f () Source #

Skip zero or more instances of an action.

skipMany1 :: Alternative f => f a -> f () Source #

Skip one or more instances of an action.

eitherP :: Alternative f => f a -> f b -> f (Either a b) Source #

Combine two alternatives.

feed :: Monoid i => IResult i r -> i -> IResult i r Source #

If a parser has returned a Partial result, supply it with more input.

satisfyElem :: forall t. Chunk t => (ChunkElem t -> Bool) -> Parser t (ChunkElem t) Source #

The parser satisfyElem p succeeds for any chunk element for which the predicate p returns True. Returns the element that is actually parsed.

endOfInput :: forall t. Chunk t => Parser t () Source #

Match only if all input has been consumed.

atEnd :: Chunk t => Parser t Bool Source #

Return an indication of whether the end of input has been reached.

lookAhead :: Parser i a -> Parser i a Source #

Apply a parser without consuming any input.