Safe Haskell | None |
---|---|
Language | GHC2021 |
Efficient type-level bytestring parsing via chunking.
See Bytes
for an explanation on the chunking design.
On mismatch, the index of the failing byte and its value are returned. (This is over-engineered to be extremely efficient.)
Type classes take a Natural
for tracking the current index in the type-level
bytestring. We do this on the type level for performance. Use @0
when
calling.
The parsers take an error wrapper function to enable wrapping the error into any parser with confidence that it won't do extra allocations/wrapping.
The parsers here either return the unit ()
or a pretty error. No Fail#
.
TODO check generated Core, assembly
Synopsis
- class ParseReifyBytesW64 (idx :: Natural) (bs :: [Natural]) where
- parseReifyBytesW64 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) ()
- class ParseReifyBytesW32 (idx :: Natural) (bs :: [Natural]) where
- parseReifyBytesW32 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) ()
- class ParseReifyBytesW16 (idx :: Natural) (bs :: [Natural]) where
- parseReifyBytesW16 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) ()
- class ParseReifyBytesW8 (idx :: Natural) (bs :: [Natural]) where
- parseReifyBytesW8 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) ()
Documentation
class ParseReifyBytesW64 (idx :: Natural) (bs :: [Natural]) where Source #
Parse a type-level bytestring, largest grouping Word64
.
parseReifyBytesW64 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source #
Instances
ParseReifyBytesW32 idx bs => ParseReifyBytesW64 idx bs Source # | Try to group |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW64 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # | |
(ReifyW8 b0, ReifyW8 b1, ReifyW8 b2, ReifyW8 b3, ReifyW8 b4, ReifyW8 b5, ReifyW8 b6, ReifyW8 b7, KnownNat idx, ParseReifyBytesW64 (idx + 8) bs) => ParseReifyBytesW64 idx (b0 ': (b1 ': (b2 ': (b3 ': (b4 ': (b5 ': (b6 ': (b7 ': bs)))))))) Source # | Enough bytes to make a |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW64 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # |
class ParseReifyBytesW32 (idx :: Natural) (bs :: [Natural]) where Source #
Parse a type-level bytestring, largest grouping Word32
.
parseReifyBytesW32 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source #
Instances
ParseReifyBytesW16 idx bs => ParseReifyBytesW32 idx bs Source # | Try to group |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW32 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # | |
(ReifyW8 b0, ReifyW8 b1, ReifyW8 b2, ReifyW8 b3, KnownNat idx, ParseReifyBytesW32 (idx + 4) bs) => ParseReifyBytesW32 idx (b0 ': (b1 ': (b2 ': (b3 ': bs)))) Source # | Enough bytes to make a |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW32 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # |
class ParseReifyBytesW16 (idx :: Natural) (bs :: [Natural]) where Source #
Parse a type-level bytestring, largest grouping Word16
.
parseReifyBytesW16 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source #
Instances
ParseReifyBytesW8 idx bs => ParseReifyBytesW16 idx bs Source # | Parse byte-by-byte next. |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW16 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # | |
(ReifyW8 b0, ReifyW8 b1, KnownNat idx, ParseReifyBytesW16 (idx + 2) bs) => ParseReifyBytesW16 idx (b0 ': (b1 ': bs)) Source # | Enough bytes to make a |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW16 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # |
class ParseReifyBytesW8 (idx :: Natural) (bs :: [Natural]) where Source #
Serialize a type-level bytestring, byte-by-byte.
parseReifyBytesW8 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source #
Instances
ParseReifyBytesW8 idx ('[] :: [Natural]) Source # | End of the line. |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW8 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # | |
(ReifyW8 b0, KnownNat idx, ParseReifyBytesW8 (idx + 1) bs) => ParseReifyBytesW8 idx (b0 ': bs) Source # | Parse the next byte. |
Defined in Bytezap.Parser.Struct.TypeLits.Bytes parseReifyBytesW8 :: forall (st :: ZeroBitType). ParserT st (Int, Word8) () Source # |