License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
A very simple bytearray parser related to Parsec and Attoparsec
Simple example:
> parse ((,,) <$> take 2 <*> byte 0x20 <*> (bytes "abc" *> anyByte)) "xx abctest" ParseOK "est" ("xx", 116)
Synopsis
- data Parser byteArray a
- data Result byteArray a
- parse :: ByteArrayAccess byteArray => Parser byteArray a -> byteArray -> Result byteArray a
- parseFeed :: (ByteArrayAccess byteArray, Monad m) => m (Maybe byteArray) -> Parser byteArray a -> byteArray -> m (Result byteArray a)
- hasMore :: ByteArray byteArray => Parser byteArray Bool
- byte :: ByteArray byteArray => Word8 -> Parser byteArray ()
- anyByte :: ByteArray byteArray => Parser byteArray Word8
- bytes :: (Show ba, Eq ba, ByteArray ba) => ba -> Parser ba ()
- take :: ByteArray byteArray => Int -> Parser byteArray byteArray
- takeWhile :: ByteArray byteArray => (Word8 -> Bool) -> Parser byteArray byteArray
- takeAll :: ByteArray byteArray => Parser byteArray byteArray
- skip :: ByteArray byteArray => Int -> Parser byteArray ()
- skipWhile :: ByteArray byteArray => (Word8 -> Bool) -> Parser byteArray ()
- skipAll :: ByteArray byteArray => Parser byteArray ()
- takeStorable :: (ByteArray byteArray, Storable d) => Parser byteArray d
Documentation
data Parser byteArray a Source #
Simple ByteString parser structure
Instances
Monad (Parser byteArray) Source # | |
Functor (Parser byteArray) Source # | |
MonadFail (Parser byteArray) Source # | |
Defined in Data.ByteArray.Parse | |
Applicative (Parser byteArray) Source # | |
Defined in Data.ByteArray.Parse pure :: a -> Parser byteArray a # (<*>) :: Parser byteArray (a -> b) -> Parser byteArray a -> Parser byteArray b # liftA2 :: (a -> b -> c) -> Parser byteArray a -> Parser byteArray b -> Parser byteArray c # (*>) :: Parser byteArray a -> Parser byteArray b -> Parser byteArray b # (<*) :: Parser byteArray a -> Parser byteArray b -> Parser byteArray a # | |
Alternative (Parser byteArray) Source # | |
MonadPlus (Parser byteArray) Source # | |
data Result byteArray a Source #
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
run the Parser
parse :: ByteArrayAccess byteArray => Parser byteArray a -> byteArray -> Result byteArray a Source #
Run a Parser on a ByteString and return a Result
parseFeed :: (ByteArrayAccess byteArray, Monad m) => m (Maybe byteArray) -> Parser byteArray a -> byteArray -> m (Result byteArray a) Source #
Run a parser on an @initial byteArray.
If the Parser need more data than available, the @feeder function is automatically called and fed to the More continuation.
Parser methods
byte :: ByteArray byteArray => Word8 -> Parser byteArray () Source #
Parse a specific byte at current position
if the byte is different than the expected on, this parser will raise a failure.
bytes :: (Show ba, Eq ba, ByteArray ba) => ba -> Parser ba () 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 :: ByteArray byteArray => Int -> Parser byteArray byteArray Source #
Take @n bytes from the current position in the stream
takeWhile :: ByteArray byteArray => (Word8 -> Bool) -> Parser byteArray byteArray Source #
Take bytes while the @predicate hold from the current position in the stream
takeAll :: ByteArray byteArray => Parser byteArray byteArray Source #
Take the remaining bytes from the current position in the stream
skip :: ByteArray byteArray => Int -> Parser byteArray () Source #
Skip @n bytes from the current position in the stream
skipWhile :: ByteArray byteArray => (Word8 -> Bool) -> Parser byteArray () Source #
Skip bytes while the @predicate hold from the current position in the stream