bytesmith-0.2.0.1: Nonresumable byte parser

Safe HaskellNone
LanguageHaskell2010

Data.Bytes.Parser

Contents

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

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

A non-resumable parser.

Constructors

Parser 

Fields

Instances
Monad (Parser e s :: Type -> 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 #

fail :: String -> Parser e s a #

Functor (Parser e s :: Type -> 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 #

Applicative (Parser e s :: Type -> 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 #

Monoid e => Alternative (Parser e s :: Type -> 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] #

data Result e a Source #

The result of running a parser.

Constructors

Failure e

An error message indicating what went wrong.

Success !a !Int

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

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

Defined in Data.Bytes.Parser

Methods

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

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

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

Defined in Data.Bytes.Parser

Methods

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

show :: Result e a -> String #

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

Run Parsers

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 slice of a byte array. This can succeed even if the entire slice was not consumed by the parser.

parseBytesST :: 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.

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.

Skip

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

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

Match

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

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

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.

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

:: (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, parseBytesST, and endOfInput. It is provided as a single combinator because for convenience and because it is easy 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.

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) 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) 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 #

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 #