bytezap-1.6.0: Bytestring builder with zero intermediate allocation
Safe HaskellNone
LanguageGHC2021

Bytezap.Parser.Struct

Description

Struct parser.

We do still have to do failure checking, because unlike C we check some types (e.g. bitfields). Hopefully inlining can remove those checks when unnecessary.

Synopsis

Documentation

type STMode s = State# s Source #

type ParserT# (st :: ZeroBitType) e a Source #

Arguments

 = ForeignPtrContents

pointer provenance (does not change)

-> Addr#

base address (does not change)

-> Int#

cursor offset from base

-> st

state token

-> Res# st e a

result

newtype ParserT (st :: ZeroBitType) e a Source #

Like flatparse, but no buffer length (= no buffer overflow checking), and no Addr# on success (= no dynamic length parses).

Unlike flatparse, we separate base address from offset, rather than adding them. This fits the unaligned Addr# primops (added in GHC 9.10) better, and in my head should hopefully assist in emitting immediates where possible for offsets on the assembly level.

Combining them like in flatparse might be faster; but I really don't know how to find out, without doing both and comparing various examples. After a lot of scratching my head, I think this is most appropriate.

The ForeignPtrContents is for keeping the Addr# data in scope.

Constructors

ParserT 

Fields

Instances

Instances details
Functor (ParserT st e) Source # 
Instance details

Defined in Bytezap.Parser.Struct

Methods

fmap :: (a -> b) -> ParserT st e a -> ParserT st e b #

(<$) :: a -> ParserT st e b -> ParserT st e a #

type Parser = ParserT PureMode Source #

The type of pure parsers.

type ParserIO = ParserT IOMode Source #

The type of parsers which can embed IO actions.

type ParserST s = ParserT (STMode s) Source #

The type of parsers which can embed ST actions.

type Res# (st :: ZeroBitType) e a = (# st, ResI# e a #) Source #

Primitive parser result wrapped with a state token.

You should rarely need to manipulate values of this type directly. Use the provided bidirectional pattern synonyms OK#, Fail# and Err#.

type ResI# e a = (# (# a #) | (# #) | (# e #) #) Source #

Primitive parser result.

Like flatparse, but no Addr# on success.

pattern OK# :: st -> a -> Res# st e a Source #

Res# constructor for a successful parse. Contains the return value and a state token.

pattern Fail# :: st -> Res# st e a Source #

Res# constructor for recoverable failure. Contains only a state token.

pattern Err# :: st -> e -> Res# st e a Source #

Res# constructor for errors which are by default non-recoverable. Contains the error, plus a state token.

unsafeRunParserBs :: forall a e. ByteString -> Parser e a -> Result e a Source #

caller must guarantee that buffer is long enough for parser!!

unsafeRunParserPtr :: forall a e. Ptr Word8 -> Parser e a -> Result e a Source #

caller must guarantee that buffer is long enough for parser!!

unsafeRunParserFPtr :: forall a e. ForeignPtr Word8 -> Parser e a -> Result e a Source #

caller must guarantee that buffer is long enough for parser!!

unsafeRunParser' :: forall a e. Addr# -> ForeignPtrContents -> Parser e a -> Result e a Source #

caller must guarantee that buffer is long enough for parser!!

data Result e a Source #

Higher-level boxed data type for parsing results.

Constructors

OK a

Contains return value.

Fail

Recoverable-by-default failure.

Err !e

Unrecoverable-by-default error.

Instances

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

Defined in Bytezap.Parser.Struct

Methods

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

show :: Result e a -> String #

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

constParse :: forall a (st :: ZeroBitType) e. a -> ParserT st e a Source #

can't provide via pure as no Applicative

sequenceParsers :: forall a b c (st :: ZeroBitType) e. Int -> (a -> b -> c) -> ParserT st e a -> ParserT st e b -> ParserT st e c Source #

prim :: forall a (st :: ZeroBitType) e. Prim' a => ParserT st e a Source #

lit :: forall a (st :: ZeroBitType) e. Eq a => a -> ParserT st e a -> ParserT st e () Source #

parse literal

withLit :: forall a (st :: ZeroBitType) e r. Eq a => Int# -> a -> ParserT st e a -> ParserT st e r -> ParserT st e r Source #

parse literal (CPS)

withLitErr :: forall a (st :: ZeroBitType) r. (Integral a, FiniteBits a) => Int# -> a -> Int -> (Addr# -> Int# -> a) -> ParserT st (Int, Word8) r -> ParserT st (Int, Word8) r Source #

parse literal, return first (leftmost) failing byte on error (CPS)

This can be used to parse large literals via chunking, rather than byte-by-byte, while retaining useful error behaviour.

We don't check equality with XOR even though we use that when handling errors, because it's hard to tell if it would be faster with modern CPUs and compilers.

firstNonMatchByteIdx :: FiniteBits a => a -> a -> Int Source #

Given two non-equal words wActual and wExpect, return the index of the first non-matching byte. Zero indexed.

If both words are equal, returns word_size (e.g. 4 for Word32).

unsafeByteAt :: (Num a, Bits a) => a -> Int -> a Source #

Get the byte at the given index.

The return value is guaranteed to be 0x00 - 0xFF (inclusive).

TODO meaning based on endianness?