parsley-0.1.1.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

Parsley.Selective

Description

A version of the Selective combinators as described in Selective Applicative Functors (Mokhov et al. 2019).

Like the Applicative and Alternative combinators, these cannot be properly described by the Selective typeclass, since the API relies on Template Haskell code being used by Applicative.

Since: 0.1.0.0

Synopsis

Documentation

branch Source #

Arguments

:: Parser (Either a b)

The first parser to execute

-> Parser (a -> c)

The parser to execute if the first returned a Left

-> Parser (b -> c)

The parser to execute if the first returned a Right

-> Parser c 

One of the core Selective operations. The behaviour of branch p l r is to first to parse p, if it fails then the combinator fails. If p succeeded then if its result is a Left, then the parser l is executed and applied to the result of p, otherwise r is executed and applied to the right from a Right.

Crucially, only one of l or r will be executed on p's success.

Since: 0.1.0.0

select :: Parser (Either a b) -> Parser (a -> b) -> Parser b Source #

Similar to branch, except the given branch is only executed on a Left returned.

select p q = branch p q (pure id)

Since: 0.1.0.0

(>??>) :: Parser a -> Parser (a -> Bool) -> Parser a infixl 4 Source #

This combinator is used for filtering. Given px >??> pf, if px succeeds, then pf will be attempted too. Then the result of px is given to pf's. If the function returns true then the parser succeeds and returns the result of px, otherwise it will fail.

Since: 0.1.0.0

filteredBy :: ParserOps rep => Parser a -> rep (a -> Bool) -> Parser a Source #

An alias for (>?>).

Since: 0.1.0.0

(>?>) :: ParserOps rep => Parser a -> rep (a -> Bool) -> Parser a infixl 4 Source #

This combinator is used for filtering, similar to (>??>) except the predicate is given without parsing anything.

px >?> f = px >??> pure f

Since: 0.1.0.0

predicate :: ParserOps rep => rep (a -> Bool) -> Parser a -> Parser b -> Parser b -> Parser b Source #

Similar to an if statement: predicate f p t e first parses p and collects its result x. If f x is True then t is parsed, else e is parsed.

Since: 0.1.0.0

(<?:>) :: Parser Bool -> (Parser a, Parser a) -> Parser a infixl 4 Source #

A "ternary" combinator, essentially predicate given the identity function.

Since: 0.1.0.0

conditional Source #

Arguments

:: ParserOps rep 
=> [(rep (a -> Bool), Parser b)]

A list of predicates and their outcomes

-> Parser a

A parser whose result is used to choose an outcome

-> Parser b

A parser who will be executed if no predicates succeed

-> Parser b 

conditional fqs p def first parses p, then it will try each of the predicates in fqs in turn until one of them returns True. The corresponding parser for the first predicate that succeeded is then executes, or if none of the predicates succeeded then the def parser is executed.

Since: 0.1.0.0

match Source #

Arguments

:: (Eq a, Lift a) 
=> [a]

The domain of the function given as the third argument

-> Parser a

The parser whose result will be given to the function

-> (a -> Parser b)

A function uses to generate the parser to execute

-> Parser b

A parser to execute if the result is not in the domain of the function

-> Parser b 

The match combinator can be thought of as a restricted form of (>>=), where there is a fixed domain on the valid outputs of the second argument.

More concretely, match dom p f def first parses p, and, if its result is an element of the list dom, its result is applied to the function f and the resulting parser is executed. If the result was not in dom, then def will be executed.

Note: To eliminate the dynamic nature of the operation, every possible outcome of the parser is enumerated and tried in turn.

Since: 0.1.0.0

(||=) :: (Enum a, Bounded a, Eq a, Lift a) => Parser a -> (a -> Parser b) -> Parser b infixl 1 Source #

This combinator, known as sbind in the literature, is best avoided for efficiency sake. It is built on match, but where the domain of the function is all of the possible values of the datatype. This means the type must be finite, or else this combinator would never terminate.

The problem with the combinator is not so much that it takes linear time to take the right branch (as opposed to monadic (>>=)) but that it generates a massive amount of code when the datatype gets too big. For instance, using it for Char would generate a 66535-way case split!

The role this combinator fulfils is the branching behaviour that monadic operations can provide. For the persistence or duplication of data that monads can provide, bind is a much better alternative.

Since: 0.1.0.0

when :: Parser Bool -> Parser () -> Parser () Source #

This combinator will only execute its second argument if the first one returned True.

Since: 0.1.0.0

while :: Parser Bool -> Parser () Source #

The fixed-point of the when combinator: it will continuously parse its argument until either it fails (in which case it fails), or until it returns False.

Since: 0.1.0.0

fromMaybeP :: Parser (Maybe a) -> Parser a -> Parser a Source #

Given fromMaybeP p def, if p returns a Nothing then def is executed, otherwise the result of p will be returned with the Just removed.

Since: 0.1.0.0