bsparse-0.0.5: A simple unassuming parser for bytestring

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.ByteString.Parse

Contents

Description

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)

Synopsis

Documentation

data Parser a Source

Simple ByteString parser structure

data Result 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

Instances

Show a => Show (Result a) 

run the Parser

parse :: Parser a -> ByteString -> Result a Source

Run a Parser on a ByteString and return a Result

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.

anyByte :: Parser Word8 Source

Get the next byte from the parser

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

skip :: Int -> Parser () Source

Skip @n bytes from the current position in the stream

skipWhile :: (Word8 -> Bool) -> Parser () Source

Skip bytes while the @predicate hold from the current position in the stream

skipAll :: Parser () Source

Skip all the remaining bytes from the current position in the stream

takeStorable :: Storable d => Parser d Source

Take a storable from the current position in the stream