Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provide a simple resumable Parser
, which is suitable for binary protocol and simple textual protocol parsing.
You can use Alternative
instance to do backtracking, each branch will either succeed and may consume some input, or fail without consume anything. It's recommend to use peek
to avoid backtracking if possible to get high performance.
Synopsis
- data Result a
- data Parser a
- parse :: Parser a -> Bytes -> Either String a
- parse' :: Parser a -> Bytes -> (Bytes, Either String a)
- parseChunk :: Parser a -> Bytes -> Result a
- parseChunks :: Monad m => m Bytes -> Parser a -> Bytes -> m (Bytes, Either String a)
- finishParsing :: Result a -> (Bytes, Either String a)
- runAndKeepTrack :: Parser a -> Parser (Result a, [Bytes])
- ensureN :: Int -> Parser ()
- endOfInput :: Parser Bool
- decodePrim :: forall a. UnalignedAccess a => Parser a
- decodePrimLE :: forall a. UnalignedAccess (LE a) => Parser a
- decodePrimBE :: forall a. UnalignedAccess (BE a) => Parser a
- scan :: s -> (s -> Word8 -> Maybe s) -> Parser Bytes
- scanChunks :: s -> (s -> Bytes -> Either s (Bytes, Bytes)) -> Parser Bytes
- peekMaybe :: Parser (Maybe Word8)
- peek :: Parser Word8
- satisfy :: (Word8 -> Bool) -> Parser Word8
- satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
- word8 :: Word8 -> Parser ()
- anyWord8 :: Parser Word8
- endOfLine :: Parser ()
- skip :: Int -> Parser ()
- skipWhile :: (Word8 -> Bool) -> Parser ()
- skipSpaces :: Parser ()
- take :: 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 ()
- uint :: Integral a => Parser a
- int :: Integral a => Parser a
- hex :: (Integral a, Bits a) => Parser a
- rational :: Fractional a => Parser a
- float :: Parser Float
- double :: Parser Double
- scientific :: Parser Scientific
- scientifically :: (Scientific -> a) -> 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
Simple CPSed parser
Running a parser
parse' :: Parser a -> Bytes -> (Bytes, Either String a) Source #
Parse the complete input, without resupplying, return the rest bytes
parseChunks :: Monad m => m Bytes -> Parser a -> Bytes -> m (Bytes, Either String 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 String a) Source #
Finish parsing and fetch result, feed empty bytes if it's Partial
result.
Basic parsers
ensureN :: Int -> Parser () Source #
Ensure that there are at least n
bytes available. If not, the
computation will escape with Partial
.
endOfInput :: Parser Bool Source #
Test whether all input has been consumed, i.e. there are no remaining undecoded bytes.
Primitive decoders
decodePrim :: forall a. UnalignedAccess a => Parser a Source #
decodePrimLE :: forall a. UnalignedAccess (LE a) => Parser a Source #
decodePrimBE :: forall a. UnalignedAccess (BE a) => Parser a Source #
More parsers
scan :: s -> (s -> Word8 -> Maybe s) -> Parser Bytes 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.
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
.
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.
Numeric parsers
Decimal
int :: Integral a => Parser a Source #
Parse a decimal number with an optional leading '+'
or '-'
sign
character.
Hex
hex :: (Integral a, Bits a) => Parser a Source #
Parse and decode an unsigned hex number. The hex digits
'a'
through 'f'
may be upper or lower case.
This parser does not accept a leading "0x"
string, and consider
sign bit part of the binary hex nibbles, i.e.
'parse hex "0xFF" == Right (-1 :: Int8)'
Fractional
rational :: Fractional a => Parser a Source #
Parse a rational number.
The syntax accepted by this parser is the same as for double
.
Note: this parser is not safe for use with inputs from untrusted
sources. An input with a suitably large exponent such as
"1e1000000000"
will cause a huge Integer
to be allocated,
resulting in what is effectively a denial-of-service attack.
In most cases, it is better to use double
or scientific
instead.
double :: Parser Double Source #
Parse a rational number and round to Double
.
This parser accepts an optional leading sign character, followed by
at least one decimal digit. The syntax similar to that accepted by
the read
function, with the exception that a trailing '.'
or
'e'
not followed by a number is not consumed.
Examples with behaviour identical to read
:
parseOnly double "3" == Right ("",1,3.0) parseOnly double "3.1" == Right ("",3,3.1) parseOnly double "3e4" == Right ("",3,30000.0) parseOnly double "3.1e4" == Right ("",5,31000.0)
parseOnly double ".3" == Left (".3",0,"takeWhile1") parseOnly double "e3" == Left ("e3",0,"takeWhile1")
Examples of differences from read
:
parseOnly double "3.foo" == Right (".foo",1,3.0) parseOnly double "3e" == Right ("e",1,3.0)
This function does not accept string representations of "NaN" or "Infinity".
scientific :: Parser Scientific Source #
Parse a scientific number.
The syntax accepted by this parser is the same as for double
.
scientifically :: (Scientific -> a) -> Parser a Source #
Parse a scientific number and convert to result using a user supply function.
The syntax accepted by this parser is the same as for double
.