bytesmith-0.3.9.1: Nonresumable byte parser
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bytes.Parser

Description

Parse non-resumable sequence of bytes. To parse a byte sequence as text, use the Ascii, Latin, and Utf8 modules instead. Functions for parsing decimal-encoded numbers are found in those modules.

Synopsis

Types

data Parser :: forall (r :: RuntimeRep). Type -> Type -> TYPE r -> Type Source #

A non-resumable parser.

Instances

Instances details
Monoid e => Alternative (Parser e s :: TYPE LiftedRep -> Type) Source #

Combines the error messages using <> when both parsers fail.

Instance details

Defined in Data.Bytes.Parser.Internal

Methods

empty :: Parser e s a #

(<|>) :: Parser e s a -> Parser e s a -> Parser e s a #

some :: Parser e s a -> Parser e s [a] #

many :: Parser e s a -> Parser e s [a] #

Applicative (Parser e s :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Bytes.Parser.Internal

Methods

pure :: a -> Parser e s a #

(<*>) :: Parser e s (a -> b) -> Parser e s a -> Parser e s b #

liftA2 :: (a -> b -> c) -> Parser e s a -> Parser e s b -> Parser e s c #

(*>) :: Parser e s a -> Parser e s b -> Parser e s b #

(<*) :: Parser e s a -> Parser e s b -> Parser e s a #

Functor (Parser e s :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Bytes.Parser.Internal

Methods

fmap :: (a -> b) -> Parser e s a -> Parser e s b #

(<$) :: a -> Parser e s b -> Parser e s a #

Monad (Parser e s :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Bytes.Parser.Internal

Methods

(>>=) :: Parser e s a -> (a -> Parser e s b) -> Parser e s b #

(>>) :: Parser e s a -> Parser e s b -> Parser e s b #

return :: a -> Parser e s a #

data Result e a Source #

The result of running a parser.

Constructors

Failure e

An error message indicating what went wrong.

Success !(Slice a)

The parsed value and the number of bytes remaining in parsed slice.

Instances

Instances details
Foldable (Result e) Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

fold :: Monoid m => Result e m -> m #

foldMap :: Monoid m => (a -> m) -> Result e a -> m #

foldMap' :: Monoid m => (a -> m) -> Result e a -> m #

foldr :: (a -> b -> b) -> b -> Result e a -> b #

foldr' :: (a -> b -> b) -> b -> Result e a -> b #

foldl :: (b -> a -> b) -> b -> Result e a -> b #

foldl' :: (b -> a -> b) -> b -> Result e a -> b #

foldr1 :: (a -> a -> a) -> Result e a -> a #

foldl1 :: (a -> a -> a) -> Result e a -> a #

toList :: Result e a -> [a] #

null :: Result e a -> Bool #

length :: Result e a -> Int #

elem :: Eq a => a -> Result e a -> Bool #

maximum :: Ord a => Result e a -> a #

minimum :: Ord a => Result e a -> a #

sum :: Num a => Result e a -> a #

product :: Num a => Result e a -> a #

Functor (Result e) Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

fmap :: (a -> b) -> Result e a -> Result e b #

(<$) :: a -> Result e b -> Result e a #

(Show e, Show a) => Show (Result e a) Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

showsPrec :: Int -> Result e a -> ShowS #

show :: Result e a -> String #

showList :: [Result e a] -> ShowS #

(Eq e, Eq a) => Eq (Result e a) Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

(==) :: Result e a -> Result e a -> Bool #

(/=) :: Result e a -> Result e a -> Bool #

data Slice a Source #

Slicing metadata (an offset and a length) accompanied by a value. This does not represent a slice into the value. This type is intended to be used as the result of an executed parser. In this context the slicing metadata describe a slice into to the array (or byte array) that from which the value was parsed.

It is often useful to check the length when a parser succeeds since a non-zero length indicates that there was additional unconsumed input. The offset is only ever needed to construct a new slice (via Bytes or SmallVector) from the remaining input.

Constructors

Slice !Int !Int a 

Instances

Instances details
Foldable Slice Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

fold :: Monoid m => Slice m -> m #

foldMap :: Monoid m => (a -> m) -> Slice a -> m #

foldMap' :: Monoid m => (a -> m) -> Slice a -> m #

foldr :: (a -> b -> b) -> b -> Slice a -> b #

foldr' :: (a -> b -> b) -> b -> Slice a -> b #

foldl :: (b -> a -> b) -> b -> Slice a -> b #

foldl' :: (b -> a -> b) -> b -> Slice a -> b #

foldr1 :: (a -> a -> a) -> Slice a -> a #

foldl1 :: (a -> a -> a) -> Slice a -> a #

toList :: Slice a -> [a] #

null :: Slice a -> Bool #

length :: Slice a -> Int #

elem :: Eq a => a -> Slice a -> Bool #

maximum :: Ord a => Slice a -> a #

minimum :: Ord a => Slice a -> a #

sum :: Num a => Slice a -> a #

product :: Num a => Slice a -> a #

Functor Slice Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

fmap :: (a -> b) -> Slice a -> Slice b #

(<$) :: a -> Slice b -> Slice a #

Show a => Show (Slice a) Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

showsPrec :: Int -> Slice a -> ShowS #

show :: Slice a -> String #

showList :: [Slice a] -> ShowS #

Eq a => Eq (Slice a) Source # 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

(==) :: Slice a -> Slice a -> Bool #

(/=) :: Slice a -> Slice a -> Bool #

Run Parsers

Result

parseByteArray :: (forall s. Parser e s a) -> ByteArray -> Result e a Source #

Variant of parseBytes that accepts an unsliced ByteArray.

parseBytes :: forall e a. (forall s. Parser e s a) -> Bytes -> Result e a Source #

Parse a byte sequence. This can succeed even if the entire slice was not consumed by the parser.

parseBytesEffectfully :: Parser e s a -> Bytes -> ST s (Result e a) Source #

Variant of parseBytes that allows the parser to be run as part of an existing effectful context.

parseBytesEither :: forall e a. (forall s. Parser e s a) -> Bytes -> Either e a Source #

Variant of parseBytes that discards the new offset and the remaining length. This does not, however, require the remaining length to be zero. Use endOfInput to accomplish that.

parseBytesMaybe :: forall e a. (forall s. Parser e s a) -> Bytes -> Maybe a Source #

Variant of parseBytesEither that discards the error message on failure. Just like parseBytesEither, this does not impose any checks on the length of the remaining input.

One Byte

any :: e -> Parser e s Word8 Source #

Consumes and returns the next byte in the input. Fails if no characters are left.

Many Bytes

take :: e -> Int -> Parser e s Bytes Source #

Take the given number of bytes. Fails if there is not enough remaining input.

takeWhile :: (Word8 -> Bool) -> Parser e s Bytes Source #

Take while the predicate is matched. This is always inlined. This always succeeds.

takeTrailedBy :: e -> Word8 -> Parser e s Bytes Source #

Take bytes until the specified byte is encountered. Consumes the matched byte as well. Fails if the byte is not present. Visually, the cursor advancement and resulting Bytes for takeTrailedBy 0x19 look like this:

 0x10 0x13 0x08 0x15 0x19 0x23 0x17 | input
|---->---->---->---->----|          | cursor
{----*----*----*----}               | result bytes

Skip

skipWhile :: (Word8 -> Bool) -> Parser e s () Source #

Skip while the predicate is matched. This is always inlined.

skipTrailedBy :: e -> Word8 -> Parser e s () Source #

Skip all characters until the character from the is encountered and then consume the matching byte as well.

skipTrailedBy2 Source #

Arguments

:: e

Error message

-> Word8

First trailer, False indicates that this was encountered

-> Word8

Second trailer, True indicates that this was encountered

-> Parser e s Bool 

Skip all bytes until either of the bytes in encountered. Then, consume the matched byte. True indicates that the first argument byte was encountered. False indicates that the second argument byte was encountered.

skipTrailedBy2# Source #

Arguments

:: e

Error message

-> Word8

First trailer, 0 indicates that this was encountered

-> Word8

Second trailer, 1 indicates that this was encountered

-> Parser e s Int# 

skipTrailedBy3# Source #

Arguments

:: e

Error message

-> Word8

First trailer, 0 indicates that this was encountered

-> Word8

Second trailer, 1 indicates that this was encountered

-> Word8

Third trailer, 2 indicates that this was encountered

-> Parser e s Int# 

Match

byteArray :: e -> ByteArray -> Parser e s () Source #

bytes :: e -> Bytes -> Parser e s () Source #

Consume input matching the byte sequence.

satisfy :: e -> (Word8 -> Bool) -> Parser e s Word8 Source #

The parser satisfy p succeeds for any byte for which the predicate p returns True. Returns the byte that is actually parsed.

satisfyWith :: e -> (Word8 -> a) -> (a -> Bool) -> Parser e s 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.

cstring :: e -> CString -> Parser e s () Source #

Consume input matching the NUL-terminated C String.

End of Input

endOfInput :: e -> Parser e s () Source #

Fails if there is still more input remaining.

isEndOfInput :: Parser e s Bool Source #

Returns true if there are no more bytes in the input. Returns false otherwise. Always succeeds.

remaining :: Parser e s Bytes Source #

Consume all remaining bytes in the input.

peekRemaining :: Parser e s Bytes Source #

Return all remaining bytes in the input without consuming them.

Scanning

scan :: state -> (state -> Word8 -> Maybe state) -> Parser e s state 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 the initial state if the predicate returns Nothing on the first byte of input.

Note: Because this parser does not fail, do not use it with combinators such a many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

Lookahead

peek :: Parser e s (Maybe Word8) Source #

Match any byte, to perform lookahead. Returns Nothing if end of input has been reached. Does not consume any input.

Note: Because this parser does not fail, do not use it with combinators such as many, because such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

peek' :: e -> Parser e s Word8 Source #

Match any byte, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.

Control Flow

fail Source #

Arguments

:: e

Error message

-> Parser e s a 

Fail with the provided error message.

orElse :: Parser x s a -> Parser e s a -> Parser e s a infixl 3 Source #

There is a law-abiding instance of Alternative for Parser. However, it is not terribly useful since error messages seldom have a Monoid instance. This function is a variant of <|> that is right-biased in its treatment of error messages. Consequently, orElse lacks an identity. See attoparsec issue #122 for more discussion of this topic.

annotate :: Parser x s a -> e -> Parser e s a Source #

Annotate a parser. If the parser fails, the error will be returned.

(<?>) :: Parser x s a -> e -> Parser e s a infix 0 Source #

Infix version of annotate.

Repetition

replicate Source #

Arguments

:: forall arr e s a. (Contiguous arr, Element arr a) 
=> Int

Number of times to run the parser

-> Parser e s a

Parser

-> Parser e s (arr a) 

Replicate a parser n times, writing the results into an array of length n. For Array and SmallArray, this is lazy in the elements, so be sure the they result of the parser is evaluated appropriately to avoid unwanted thunks.

Subparsing

delimit Source #

Arguments

:: e

Error message when not enough bytes are present

-> e

Error message when delimited parser does not consume all input

-> Int

Exact number of bytes delimited parser is expected to consume

-> Parser e s a

Parser to execute in delimited context

-> Parser e s a 

Run a parser in a delimited context, failing if the requested number of bytes are not available or if the delimited parser does not consume all input. This combinator can be understood as a composition of take, effect, parseBytesEffectfully, and endOfInput. It is provided as a single combinator because for convenience and because it is easy to make mistakes when manually assembling the aforementioned parsers. The pattern of prefixing an encoding with its length is common. This is discussed more in attoparsec issue #129.

delimit e1 e2 n remaining === take e1 n

measure :: Parser e s a -> Parser e s (Int, a) Source #

Augment a parser with the number of bytes that were consume while it executed.

measure_ :: Parser e s a -> Parser e s Int Source #

Run a parser and discard the result, returning instead the number of bytes that the parser consumed.

measure_# :: Parser e s a -> Parser e s Int# Source #

Variant of measure_ with an unboxed result.

Lift Effects

effect :: ST s a -> Parser e s a Source #

Lift an effectful computation into a parser.

Box Result

boxWord32 :: Parser e s Word# -> Parser e s Word32 Source #

Convert a Word# parser to a Word32 parser. Precondition: the argument parser only returns words less than 4294967296.

boxIntPair :: Parser e s (# Int#, Int# #) -> Parser e s (Int, Int) Source #

Convert a (# Int#, Int# #) parser to a (Int,Int) parser.

Unbox Result

unboxWord32 :: Parser e s Word32 -> Parser e s Word# Source #

Convert a Word32 parser to a Word# parser.

unboxIntPair :: Parser e s (Int, Int) -> Parser e s (# Int#, Int# #) Source #

Convert a (Int,Int) parser to a (# Int#, Int# #) parser.

Specialized Bind

Sometimes, GHC ends up building join points in a way that boxes arguments unnecessarily. In this situation, special variants of monadic >>= can be helpful. If C#, I#, etc. never get used in your original source code, GHC will not introduce them.

bindFromCharToLifted :: Parser s e Char# -> (Char# -> Parser s e a) -> Parser s e a Source #

bindFromLiftedToIntPair :: Parser s e a -> (a -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #) Source #

bindFromLiftedToInt :: Parser s e a -> (a -> Parser s e Int#) -> Parser s e Int# Source #

bindFromIntToIntPair :: Parser s e Int# -> (Int# -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #) Source #

bindFromCharToIntPair :: Parser s e Char# -> (Char# -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #) Source #

bindFromMaybeCharToIntPair :: Parser s e (# (# #) | Char# #) -> ((# (# #) | Char# #) -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #) Source #

bindFromMaybeCharToLifted :: Parser s e (# (# #) | Char# #) -> ((# (# #) | Char# #) -> Parser s e a) -> Parser s e a Source #

Specialized Pure

pureIntPair :: (# Int#, Int# #) -> Parser s e (# Int#, Int# #) Source #

Specialized Fail

failIntPair :: e -> Parser e s (# Int#, Int# #) Source #