License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A very simple bytestring parser related to Parsec and Attoparsec
Simple example:
> parse ((,) <$> take 2 <*> byte 0x20 <*> (bytes "abc" *> anyByte)) "xx abctest" ParseOK "est" ("xx", 116)
- data Parser a
- data Result a
- = ParseFail String
- | ParseMore (ByteString -> Result a)
- | ParseOK ByteString a
- parse :: Parser a -> ByteString -> Result a
- parseFeed :: Monad m => m ByteString -> Parser a -> ByteString -> m (Result a)
- byte :: Word8 -> Parser ()
- anyByte :: Parser Word8
- bytes :: ByteString -> Parser ()
- take :: Int -> Parser ByteString
- takeWhile :: (Word8 -> Bool) -> Parser ByteString
- takeAll :: Parser ByteString
- skip :: Int -> Parser ()
- skipWhile :: (Word8 -> Bool) -> Parser ()
- skipAll :: Parser ()
Documentation
Simple ByteString parser structure
Simple parsing result, that represent respectively:
- failure: with the error message
- continuation: that need for more input data
- success: the remaining unparsed data and the parser value
ParseFail String | |
ParseMore (ByteString -> Result a) | |
ParseOK ByteString a |
run the Parser
parseFeed :: Monad m => m ByteString -> Parser a -> ByteString -> m (Result a) Source
Run a parser on an @initial ByteString.
If the Parser need more data than available, the @feeder function is automatically called and fed to the More continuation.
Parser methods
byte :: Word8 -> Parser () Source
Parse a specific byte at current position
if the byte is different than the expected on, this parser will raise a failure.
bytes :: ByteString -> Parser () Source
Parse a sequence of bytes from current position
if the following bytes don't match the expected bytestring completely, the parser will raise a failure
take :: Int -> Parser ByteString Source
Take @n bytes from the current position in the stream
takeWhile :: (Word8 -> Bool) -> Parser ByteString Source
Take bytes while the @predicate hold from the current position in the stream
takeAll :: Parser ByteString Source
Take the remaining bytes from the current position in the stream