xmonad-contrib-0.17.1.9: Community-maintained extensions for xmonad
Copyright(c) 2021 Tony Zorman
LicenseBSD3
MaintainerTony Zorman <soliditsallgood@mailbox.org>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Util.Parser

Description

A small wrapper around the ReadP parser combinator in base, providing a more intuitive behaviour. While it's theoretically nice that ReadP is actually commutative, this makes a lot of parsing operations rather awkward—more often than not, one only wants the argument that's parsed "first".

Due to the left-biased nature of the chosen semigroup implementation, using functions like many or optional from Control.Applicative now yields more consistent behaviour with other parser combinator libraries.

Synopsis

Usage

NOTE: This module is mostly intended for developing of other modules. If you are a users, you probably won't find much use here—you have been warned.

The high-level API tries to stay as close to ReadP as possible. If you are familiar with that then no functions here should surprise you.

One notable usability difference when forcing left-biasedness is when one wants to disambiguate a parse. For normal ReadP usage this happens after the actual parsing stage by going through the list of successful parses. For Parser it does when constructing the relevant combinators, leading to only one successful parse. As an example, consider the ReadP-based parser

pLangle = ReadP.string "<"
pLongerSequence = ReadP.char '<' *> ReadP.string "f" <* ReadP.char '>'
pCombination = pLangle ReadP.+++ pLongerSequence

Parsing the string "<f>" will return

>>> ReadP.readP_to_S pCombination "<f>"
[("<","f>"),("f","")]

One would now need to, for example, filter for the second (leftover) string being empty and take the head of the resulting list (which may still have more than one element).

With Parser, the same situation would look like the following

pLangle' = string "<"
pLongerSequence' = char '<' *> string "f" <* char '>'
pCombination' = pLongerSequence' <> pLangle'

Notice how pLangle' and pLongerSequence' have traded places—since we are not forcing pLangle' to consume the entire string and (<>) is left-biased, pLongerSequence' parses a superset of pLangle'! Running runParser pCombination' now yields the expected result:

>>> runParser pCombination' "<f>"
Just "f"

One might also define pLangle' as string "<" <* eof, which would enable a definition of pCombination' = pLangle' <> pLongerSequence'.

For example uses, see XMonad.Util.EZConfig or XMonad.Prompt.OrgMode.

Running

data Parser a Source #

Instances

Instances details
Alternative Parser Source # 
Instance details

Defined in XMonad.Util.Parser

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Applicative Parser Source # 
Instance details

Defined in XMonad.Util.Parser

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Functor Parser Source # 
Instance details

Defined in XMonad.Util.Parser

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Monad Parser Source # 
Instance details

Defined in XMonad.Util.Parser

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

a ~ String => IsString (Parser a) Source #

When -XOverloadedStrings is on, treat a string s as the parser string s, when appropriate. This allows one to write things like "a" *> otherParser instead of string "a" *> otherParser.

Instance details

Defined in XMonad.Util.Parser

Methods

fromString :: String -> Parser a #

Monoid (Parser a) Source # 
Instance details

Defined in XMonad.Util.Parser

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

Semigroup (Parser a) Source # 
Instance details

Defined in XMonad.Util.Parser

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

runParser :: Parser a -> String -> Maybe a Source #

Run a parser on a given string.

Primitive Parsers

pfail :: Parser a Source #

Always fails

eof :: Parser () Source #

Succeeds if and only if we are at the end of input.

num :: (Read a, Integral a) => Parser a Source #

Parse an integral number.

char :: Char -> Parser Char Source #

Parse and return the specified character.

string :: String -> Parser String Source #

Parse and return the specified string.

skipSpaces :: Parser () Source #

Skip all whitespace.

get :: Parser Char Source #

Consume and return the next character. Fails if there is no input left.

look :: Parser String Source #

Look-ahead: return the part of the input that is left, without consuming it.

gather :: forall a. Parser a -> Parser (String, a) Source #

Transform a parser into one that does the same, but in addition returns the exact characters read.

>>> runParser (         string "* " $> True) "* hi"
Just True
>>> runParser (gather $ string "* " $> True) "* hi"
Just ("* ",True)

Combining Parsers

satisfy :: (Char -> Bool) -> Parser Char Source #

Consume and return the next character if it satisfies the specified predicate.

choice :: [Parser a] -> Parser a Source #

Combine all parsers in the given list in a left-biased way.

count :: Int -> Parser a -> Parser [a] Source #

count n p parses n occurrences of p in sequence and returns a list of results.

between :: Parser open -> Parser close -> Parser a -> Parser a Source #

between open close p parses open, followed by p and finally close. Only the value of p is returned.

option :: a -> Parser a -> Parser a Source #

option def p will try to parse p and, if it fails, simply return def without consuming any input.

optionally :: Parser a -> Parser () Source #

optionally p optionally parses p and always returns ().

skipMany :: Parser a -> Parser () Source #

Like many, but discard the result.

skipMany1 :: Parser a -> Parser () Source #

Like many1, but discard the result.

many1 :: Parser a -> Parser [a] Source #

Parse one or more occurrences of the given parser.

sepBy :: Parser a -> Parser sep -> Parser [a] Source #

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

sepBy1 :: Parser a -> Parser sep -> Parser [a] Source #

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

endBy :: Parser a -> Parser sep -> Parser [a] Source #

endBy p sep parses zero or more occurrences of p, separated and ended by sep.

endBy1 :: Parser a -> Parser sep -> Parser [a] Source #

endBy p sep parses one or more occurrences of p, separated and ended by sep.

munch :: (Char -> Bool) -> Parser String Source #

Parse the first zero or more characters satisfying the predicate. Always succeeds; returns an empty string if the predicate returns False on the first character of input.

munch1 :: (Char -> Bool) -> Parser String Source #

Parse the first one or more characters satisfying the predicate. Fails if none, else succeeds exactly once having consumed all the characters.

chainr :: Parser a -> Parser (a -> a -> a) -> a -> Parser a Source #

chainr p op x parses zero or more occurrences of p, separated by op. Returns a value produced by a right associative application of all functions returned by op. If there are no occurrences of p, x is returned.

chainr1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a Source #

Like chainr, but parses one or more occurrences of p.

chainl :: Parser a -> Parser (a -> a -> a) -> a -> Parser a Source #

chainl p op x parses zero or more occurrences of p, separated by op. Returns a value produced by a left associative application of all functions returned by op. If there are no occurrences of p, x is returned.

chainl1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a Source #

Like chainl, but parses one or more occurrences of p.

manyTill :: forall a end. Parser a -> Parser end -> Parser [a] Source #

manyTill p end parses zero or more occurrences of p, until end succeeds. Returns a list of values returned by p.