Copyright | (c) Dong Han 2017-2019 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Result a
- type ParseError = [Text]
- type ParseStep r = Bytes -> Result r
- newtype Parser a = Parser {
- runParser :: forall r. (ParseError -> ParseStep r) -> (a -> ParseStep r) -> ParseStep r
- (<?>) :: Text -> Parser a -> Parser a
- parse :: Parser a -> Bytes -> (Bytes, Either ParseError a)
- parse' :: Parser a -> Bytes -> Either ParseError a
- parseChunk :: Parser a -> Bytes -> Result a
- parseChunks :: Monad m => Parser a -> m Bytes -> Bytes -> m (Bytes, Either ParseError a)
- finishParsing :: Result a -> (Bytes, Either ParseError a)
- runAndKeepTrack :: Parser a -> Parser (Result a, [Bytes])
- match :: Parser a -> Parser (Bytes, a)
- ensureN :: Int -> ParseError -> Parser ()
- endOfInput :: Parser ()
- atEnd :: Parser Bool
- decodePrim :: forall a. Unaligned a => Parser a
- decodePrimLE :: forall a. Unaligned (LE a) => Parser a
- decodePrimBE :: forall a. Unaligned (BE a) => Parser a
- scan :: s -> (s -> Word8 -> Maybe s) -> Parser (Bytes, s)
- scanChunks :: forall s. s -> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s)
- peekMaybe :: Parser (Maybe Word8)
- peek :: Parser Word8
- satisfy :: (Word8 -> Bool) -> Parser Word8
- satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
- word8 :: Word8 -> Parser ()
- char8 :: Char -> Parser ()
- skipWord8 :: Parser ()
- endOfLine :: Parser ()
- skip :: Int -> Parser ()
- skipWhile :: (Word8 -> Bool) -> Parser ()
- skipSpaces :: Parser ()
- take :: Int -> Parser Bytes
- takeN :: (Word8 -> Bool) -> Int -> Parser Bytes
- takeTill :: (Word8 -> Bool) -> Parser Bytes
- takeWhile :: (Word8 -> Bool) -> Parser Bytes
- takeWhile1 :: (Word8 -> Bool) -> Parser Bytes
- bytes :: Bytes -> Parser ()
- bytesCI :: Bytes -> Parser ()
- text :: Text -> Parser ()
- isSpace :: Word8 -> Bool
- fail' :: Text -> Parser a
Parser types
Simple parsing result, that represent respectively:
- Success: the remaining unparsed data and the parsed value
- Failure: the remaining unparsed data and the error message
- Partial: that need for more input data, supply empty bytes to indicate
endOfInput
Instances
type ParseError = [Text] Source #
Type alias for error message
Simple CPSed parser
A parser takes a failure continuation, and a success one, while the success continuation is
usually composed by Monad
instance, the failure one is more like a reader part, which can
be modified via <?>
. If you build parsers from ground, a pattern like this can be used:
xxParser = do ensureN errMsg ... -- make sure we have some bytes Parser $ kf k inp -> -- fail continuation, success continuation and input ... ... kf errMsg (if input not OK) ... k ... (if we get something useful for next parser)
Running a parser
parse :: Parser a -> Bytes -> (Bytes, Either ParseError a) Source #
Parse the complete input, without resupplying, return the rest bytes
parse' :: Parser a -> Bytes -> Either ParseError a Source #
Parse the complete input, without resupplying
parseChunks :: Monad m => Parser a -> m Bytes -> Bytes -> m (Bytes, Either ParseError a) Source #
Run a parser with an initial input string, and a monadic action that can supply more input if needed.
Note, once the monadic action return empty bytes, parsers will stop drawing
more bytes (take it as endOfInput
).
finishParsing :: Result a -> (Bytes, Either ParseError a) Source #
Finish parsing and fetch result, feed empty bytes if it's Partial
result.
match :: Parser a -> Parser (Bytes, a) Source #
Return both the result of a parse and the portion of the input that was consumed while it was being parsed.
Basic parsers
ensureN :: Int -> ParseError -> Parser () Source #
Ensure that there are at least n
bytes available. If not, the
computation will escape with Partial
.
Since this parser is used in many other parsers, an extra error param is provide to attach custom error info.
endOfInput :: Parser () Source #
Test whether all input has been consumed, i.e. there are no remaining
undecoded bytes. Fail if not atEnd
.
Test whether all input has been consumed, i.e. there are no remaining undecoded bytes.
Primitive decoders
decodePrim :: forall a. Unaligned a => Parser a Source #
More parsers
scan :: s -> (s -> Word8 -> Maybe s) -> Parser (Bytes, s) Source #
A stateful scanner. The predicate consumes and transforms a
state argument, and each transformed state is passed to successive
invocations of the predicate on each byte of the input until one
returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the
predicate returns Nothing
on the first byte of input.
scanChunks :: forall s. s -> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s) Source #
peekMaybe :: Parser (Maybe Word8) Source #
Match any byte, to perform lookahead. Returns Nothing
if end of
input has been reached. Does not consume any input.
Match any byte, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.
satisfy :: (Word8 -> Bool) -> Parser Word8 Source #
The parser satisfy p
succeeds for any byte for which the
predicate p
returns True
. Returns the byte that is actually
parsed.
digit = satisfy isDigit where isDigit w = w >= 48 && w <= 57
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a Source #
The parser satisfyWith f p
transforms a byte, and succeeds if
the predicate p
returns True
on the transformed value. The
parser returns the transformed byte that was parsed.
endOfLine :: Parser () Source #
Match either a single newline byte '\n'
, or a carriage
return followed by a newline byte "\r\n"
.
skipWhile :: (Word8 -> Bool) -> Parser () Source #
Skip past input for as long as the predicate returns True
.
skipSpaces :: Parser () Source #
Skip over white space using isSpace
.
takeN :: (Word8 -> Bool) -> Int -> Parser Bytes Source #
Similar to take
, but requires the predicate to succeed on next N bytes
of input, and take N bytes(no matter if N+1 byte satisfy predicate or not).
takeTill :: (Word8 -> Bool) -> Parser Bytes Source #
Consume input as long as the predicate returns False
or reach the end of input,
and return the consumed input.
takeWhile :: (Word8 -> Bool) -> Parser Bytes Source #
Consume input as long as the predicate returns True
or reach the end of input,
and return the consumed input.