Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines our parsing monad. In the past there have been lazy and strict parsers in this module. Currently we have only the strict variant and it is used for parsing patch files.
- class (Functor m, Applicative m, Alternative m, Monad m, MonadPlus m) => ParserM m where
- take :: ParserM m => Int -> m ByteString
- parse :: ParserM m => m a -> ByteString -> Maybe (a, ByteString)
- parseStrictly :: SM a -> ByteString -> Maybe (a, ByteString)
- char :: ParserM m => Char -> m ()
- int :: ParserM m => m Int
- option :: Alternative f => a -> f a -> f a
- choice :: Alternative f => [f a] -> f a
- skipSpace :: ParserM m => m ()
- skipWhile :: ParserM m => (Char -> Bool) -> m ()
- string :: ParserM m => ByteString -> m ()
- lexChar :: ParserM m => Char -> m ()
- lexString :: ParserM m => ByteString -> m ()
- lexEof :: ParserM m => m ()
- takeTillChar :: ParserM m => Char -> m ByteString
- myLex' :: ParserM m => m ByteString
- anyChar :: ParserM m => m Char
- endOfInput :: ParserM m => m ()
- takeTill :: ParserM m => (Char -> Bool) -> m ByteString
- checkConsumes :: ParserM m => m a -> m a
- linesStartingWith :: ParserM m => Char -> m [ByteString]
- linesStartingWithEndingWith :: ParserM m => Char -> Char -> m [ByteString]
Documentation
class (Functor m, Applicative m, Alternative m, Monad m, MonadPlus m) => ParserM m where Source #
work, peekInput, parse
parse :: m a -> ByteString -> Maybe (a, ByteString) Source #
Run the parser
parse :: ParserM m => m a -> ByteString -> Maybe (a, ByteString) Source #
Run the parser
parseStrictly :: SM a -> ByteString -> Maybe (a, ByteString) Source #
parseStrictly
applies the parser functions to a string
and checks that each parser produced a result as it goes.
The strictness is in the ParserM
instance for SM
.
char :: ParserM m => Char -> m () Source #
Accepts only the specified character. Consumes a character, if available.
int :: ParserM m => m Int Source #
Parse an integer and return it. Skips leading whitespaces and | uses the efficient ByteString readInt.
option :: Alternative f => a -> f a -> f a Source #
If p
fails it returns x
, otherwise it returns the result of p
.
choice :: Alternative f => [f a] -> f a Source #
Attempts each option until one succeeds.
skipSpace :: ParserM m => m () Source #
Discards spaces until a non-space character is encountered. Always succeeds.
skipWhile :: ParserM m => (Char -> Bool) -> m () Source #
Discards any characters as long as p
returns True. Always
| succeeds.
string :: ParserM m => ByteString -> m () Source #
Only succeeds if the characters in the input exactly match str
.
lexString :: ParserM m => ByteString -> m () Source #
takeTillChar :: ParserM m => Char -> m ByteString Source #
Equivalent to takeTill (==c)
, except that it is optimized for
| the equality case.
myLex' :: ParserM m => m ByteString Source #
Like myLex
except that it is in ParserM
anyChar :: ParserM m => m Char Source #
Accepts the next character and returns it. Only fails at end of input.
endOfInput :: ParserM m => m () Source #
Only succeeds at end of input, consumes no characters.
takeTill :: ParserM m => (Char -> Bool) -> m ByteString Source #
Takes characters while p
returns True. Always succeeds.
checkConsumes :: ParserM m => m a -> m a Source #
Ensure that a parser consumes input when producing a result Causes the initial state of the input stream to be held on to while the parser runs, so use with caution.
linesStartingWith :: ParserM m => Char -> m [ByteString] Source #
This is a highly optimized way to read lines that start with a
particular character. To implement this efficiently we need access
to the parser's internal state. If this is implemented in terms of
the other primitives for the parser it requires us to consume one
character at a time. That leads to (>>=)
wasting significant
time.
linesStartingWithEndingWith :: ParserM m => Char -> Char -> m [ByteString] Source #
This is a highly optimized way to read lines that start with a
particular character, and stops when it reaches a particular |
character. See linesStartingWith
for details on why this |
defined here as a primitive.