parser-combinators-0.3.0: Lightweight package providing commonly useful parser combinators

Copyright© 2017 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Applicative.Combinators

Contents

Description

The module provides parser combinators defined for instances of Applicative and Alternative. It also re-exports functions that are commonly used in parsing from Control.Applicative with additional parsing-related comments added.

A note on backtracking

Certain parsing libraries, such as Megaparsec, do not backtrack every branch of parsing automatically for the sake of performance and better error messages. They typically backtrack only “atomic” parsers, e.g. those that match a token or several tokens in a row. To backtrack an arbitrary complex parser/branch, a special combinator should be used, typically called try. Combinators in this module are defined in terms Applicative and Alternative operations. Being quite abstract, they cannot know anything about inner workings of any concrete parsing library, and so they cannot use try.

An essential feature of the Alternative type class is the (<|>) operator that allows to express choice. In libraries that do not backtrack everything automatically, the choice operator and everything that is build on top of it require the parser of the left hand side to backtrack in order for the alternative branch of parsing to be tried. Thus it is the responsibility of the programmer to wrap more complex, composite parsers in try to achieve correct behavior.

Synopsis

Re-exports from Control.Applicative

(<|>) :: Alternative f => forall a. f a -> f a -> f a infixl 3 #

An associative binary operation

This combinator implements choice. The parser p <|> q first applies p. If it succeeds, the value of p is returned. If p fails, parser q is tried.

many :: Alternative f => forall a. f a -> f [a] #

Zero or more.

many p applies the parser p zero or more times and returns a list of the returned values of p.

identifier = (:) <$> letter <*> many (alphaNumChar <|> char '_')

some :: Alternative f => forall a. f a -> f [a] #

One or more.

some p applies the parser p one or more times and returns a list of the returned values of p.

word = some letter

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

optional p tries to apply the parser p. It will parse p or Nothing. It only fails if p fails after consuming input. On success result of p is returned inside of Just, on failure Nothing is returned.

See also: option.

Original combinators

between :: Applicative m => m open -> m close -> m a -> m a Source #

between open close p parses open, followed by p and close. Returns the value returned by p.

braces = between (symbol "{") (symbol "}")

choice :: (Foldable f, Alternative m) => f (m a) -> m a Source #

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

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

count n p parses n occurrences of p. If n is smaller or equal to zero, the parser equals to pure []. Returns a list of n values.

See also: skipCount, count'.

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

count' m n p parses from m to n occurrences of p. If n is not positive or m > n, the parser equals to pure []. Returns a list of parsed values.

Please note that m may be negative, in this case effect is the same as if it were equal to zero.

See also: count.

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

Combine two alternatives.

endBy :: Alternative m => m a -> m sep -> m [a] Source #

endBy p sep parses zero or more occurrences of p, separated and ended by sep. Returns a list of values returned by p.

cStatements = cStatement `endBy` semicolon

endBy1 :: Alternative m => m a -> m sep -> m [a] Source #

endBy1 p sep parses one or more occurrences of p, separated and ended by sep. Returns a list of values returned by p.

manyTill :: Alternative m => m a -> m end -> m [a] Source #

manyTill p end applies parser p zero or more times until parser end succeeds. Returns the list of values returned by p.

See also: skipMany, skipManyTill.

someTill :: Alternative m => m a -> m end -> m [a] Source #

someTill p end works similarly to manyTill p end, but p should succeed at least once.

See also: skipSome, skipSomeTill.

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

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

priority = option 0 (digitToInt <$> digitChar)

See also: optional.

sepBy :: Alternative m => m a -> m sep -> m [a] Source #

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

commaSep p = p `sepBy` comma

sepBy1 :: Alternative m => m a -> m sep -> m [a] Source #

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

sepEndBy :: Alternative m => m a -> m sep -> m [a] Source #

sepEndBy p sep parses zero or more occurrences of p, separated and optionally ended by sep. Returns a list of values returned by p.

sepEndBy1 :: Alternative m => m a -> m sep -> m [a] Source #

sepEndBy1 p sep parses one or more occurrences of p, separated and optionally ended by sep. Returns a list of values returned by p.

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

skipMany p applies the parser p zero or more times, skipping its result.

See also: manyTill, skipManyTill.

skipSome :: Alternative m => m a -> m () Source #

skipSome p applies the parser p one or more times, skipping its result.

See also: someTill, skipSomeTill.

skipCount :: Applicative m => Int -> m a -> m () Source #

skipCount n p parses n occurrences of p, skipping its result. If n is smaller or equal to zero, the parser equals to pure []. Returns a list of n values.

See also: count, count'.

Since: 0.3.0

skipManyTill :: Alternative m => m a -> m end -> m end Source #

skipManyTill p end applies the parser p zero or more times skipping results until parser end succeeds. Result parsed by end is then returned.

See also: manyTill, skipMany.

skipSomeTill :: Alternative m => m a -> m end -> m end Source #

skipSomeTill p end applies the parser p one or more times skipping results until parser end succeeds. Result parsed by end is then returned.

See also: someTill, skipSome.