attoparsec-0.11.3.1: Fast combinator parsing for bytestrings and text

Portabilityportable
Stabilityexperimental
Maintainerbos@serpentine.com
Safe HaskellNone

Data.Attoparsec.Combinator

Contents

Description

Useful parser combinators, similar to those provided by Parsec.

Synopsis

Combinators

try :: Parser t a -> Parser t aSource

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.

(<?>)Source

Arguments

:: Parser t a 
-> String

the name to use if parsing fails

-> Parser t a 

Name the parser, in case failure occurs.

choice :: Alternative f => [f a] -> f aSource

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 aSource

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` (symbol ",")

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'` (symbol ",")

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` (symbol ",")

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'` (symbol ",")

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.

Parsing individual chunk elements

satisfyElem :: 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.

digit = satisfyElem isDigit
    where isDigit c = c >= '0' && c <= '9'

State observation and manipulation functions

endOfInput :: Chunk t => Parser t ()Source

Match only if all input has been consumed.

atEnd :: Chunk t => Parser t BoolSource

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