bytesmith-0.1.0.0: Nonresumable byte parser

Safe HaskellNone
LanguageHaskell2010

Data.Bytes.Parser

Contents

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

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

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

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 #

data Result e a Source #

The result of running a parser.

Constructors

Failure e

An error message indicating what went wrong.

Success !a !Int !Int

The parsed value, the offset after the last consumed byte, and the number of bytes remaining in parsed slice.

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.

Build Parsers

fail Source #

Arguments

:: e

Error message

-> Parser e s a 

Fail with the provided error message.

peekAnyAscii :: e -> Parser e s Char Source #

Interpret the next byte as an ASCII-encoded character. Fails if the byte corresponds to a number above 127.

ascii :: e -> Char -> Parser e s () Source #

Only valid for characters with a Unicode code point lower than 128. This consumes a single byte, decoding it as an ASCII character.

ascii3 :: e -> Char -> Char -> Char -> Parser e s () Source #

Parse three bytes in succession.

ascii4 :: e -> Char -> Char -> Char -> Char -> Parser e s () Source #

Parse four bytes in succession.

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

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

anyAscii :: e -> Parser e s Char Source #

Interpret the next byte as an ASCII-encoded character. Fails if the byte corresponds to a number above 127.

anyAscii# :: e -> Parser e s Char# Source #

Interpret the next byte as an ASCII-encoded character. Fails if the byte corresponds to a number above 127.

anyUtf8# :: e -> Parser e s Char# Source #

Interpret the next one to four bytes as a UTF-8-encoded character. Fails if the decoded codepoint is in the range U+D800 through U+DFFF.

anyAsciiOpt :: e -> Parser e s (Maybe Char) Source #

Interpret the next byte as an ASCII-encoded character. Fails if the byte corresponds to a number above 127. Returns nothing if the end of the input has been reached.

decWord :: e -> Parser e s Word Source #

Parse a decimal-encoded number. If the number is too large to be represented by a machine word, this overflows rather than failing. This may be changed in a future release.

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

Parse a decimal-encoded 8-bit word. If the number is larger than 255, this parser fails.

decWord16 :: e -> Parser e s Word16 Source #

Parse a decimal-encoded 16-bit word. If the number is larger than 65535, this parser fails.

decWord32 :: e -> Parser e s Word32 Source #

Parse a decimal-encoded 32-bit word. If the number is larger than 4294967295, this parser fails.

hexWord16 :: e -> Parser e s Word16 Source #

Parse exactly four ASCII-encoded characters, interpretting them as the hexadecimal encoding of a 32-bit number. Note that this rejects a sequence such as 5A9, requiring 05A9 instead. This is insensitive to case.

decPositiveInteger :: e -> Parser e s Integer Source #

Parse a decimal-encoded positive integer of arbitrary size. Note: this is not implemented efficiently. This pulls in one digit at a time, multiplying the accumulator by ten each time and adding the new digit. Since arithmetic involving arbitrary-precision integers is somewhat expensive, it would be better to pull in several digits at a time, convert those to a machine-sized integer, then upcast and perform the multiplication and addition.

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.

skipUntilAsciiConsume :: e -> Char -> Parser e s () Source #

Skip bytes until the character from the ASCII plane is encountered. This does not ensure that the skipped bytes were ASCII-encoded characters.

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

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

skipAscii :: Char -> Parser e s () Source #

Skip the character any number of times. This succeeds even if the character was not present.

skipAscii1 :: e -> Char -> Parser e s () Source #

Skip the character any number of times. It must occur at least once or else this will fail.

skipAlphaAscii :: Parser e s () Source #

Skip uppercase and lowercase letters until a non-alpha character is encountered.

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

Skip uppercase and lowercase letters until a non-alpha character is encountered.

skipDigitsAscii :: Parser e s () Source #

Skip ASCII-encoded digits until a non-digit is encountered.

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

Skip uppercase and lowercase letters until a non-alpha character is encountered.

Lift Effects

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

Lift an effectful computation into a parser.

Expose Internals

cursor :: Parser e s Int Source #

Get the current offset into the chunk. Using this makes it possible to observe the internal difference between Bytes that refer to equivalent slices. Be careful.

expose :: Parser e s ByteArray Source #

Return the byte array being parsed. This includes bytes that preceed the current offset and may include bytes that go beyond the length. This is somewhat dangerous, so only use this is you know what you're doing.

unconsume :: Int -> Parser e s () Source #

Move the cursor back by n bytes. Precondition: you must have previously consumed at least n bytes.

Cut down on boxing

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

Convert a Word32 parser to a Word# parser.

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

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

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 you original source code, GHC cannot introduce them.

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

Specialization of monadic bind for parsers that return Char#.

Alternative

orElse :: Parser s e a -> Parser s e a -> Parser s e a 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 right-biased variant of <|>. Consequently, it lacks an identity. See attoparsec #122 for more discussion of this topic.