Copyright | (c) 2021 Tony Zorman |
---|---|
License | BSD3 |
Maintainer | Tony Zorman <soliditsallgood@mailbox.org> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- data Parser a
- runParser :: Parser a -> String -> Maybe a
- pfail :: Parser a
- eof :: Parser ()
- num :: (Read a, Integral a) => Parser a
- char :: Char -> Parser Char
- string :: String -> Parser String
- skipSpaces :: Parser ()
- get :: Parser Char
- look :: Parser String
- gather :: forall a. Parser a -> Parser (String, a)
- satisfy :: (Char -> Bool) -> Parser Char
- choice :: [Parser a] -> Parser a
- count :: Int -> Parser a -> Parser [a]
- between :: Parser open -> Parser close -> Parser a -> Parser a
- option :: a -> Parser a -> Parser a
- optionally :: Parser a -> Parser ()
- skipMany :: Parser a -> Parser ()
- skipMany1 :: Parser a -> Parser ()
- many1 :: Parser a -> Parser [a]
- sepBy :: Parser a -> Parser sep -> Parser [a]
- sepBy1 :: Parser a -> Parser sep -> Parser [a]
- endBy :: Parser a -> Parser sep -> Parser [a]
- endBy1 :: Parser a -> Parser sep -> Parser [a]
- munch :: (Char -> Bool) -> Parser String
- munch1 :: (Char -> Bool) -> Parser String
- chainr :: Parser a -> Parser (a -> a -> a) -> a -> Parser a
- chainr1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a
- chainl :: Parser a -> Parser (a -> a -> a) -> a -> Parser a
- chainl1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a
- manyTill :: forall a end. Parser a -> Parser end -> Parser [a]
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
Instances
Alternative Parser Source # | |
Applicative Parser Source # | |
Functor Parser Source # | |
Monad Parser Source # | |
a ~ String => IsString (Parser a) Source # | When |
Defined in XMonad.Util.Parser fromString :: String -> Parser a # | |
Monoid (Parser a) Source # | |
Semigroup (Parser a) Source # | |
Primitive Parsers
skipSpaces :: Parser () Source #
Skip all whitespace.
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 ()
.
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.