Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Machine integer parsers.
Synopsis
- anyWord8 :: ParserT st e Word8
- anyWord16 :: ParserT st e Word16
- anyWord32 :: ParserT st e Word32
- anyWord64 :: ParserT st e Word64
- anyInt8 :: ParserT st e Int8
- anyInt16 :: ParserT st e Int16
- anyInt32 :: ParserT st e Int32
- anyInt64 :: ParserT st e Int64
- anyWord :: ParserT st e Word
- anyInt :: ParserT st e Int
- anyWord16le :: ParserT st e Word16
- anyWord16be :: ParserT st e Word16
- anyWord32le :: ParserT st e Word32
- anyWord32be :: ParserT st e Word32
- anyWord64le :: ParserT st e Word64
- anyWord64be :: ParserT st e Word64
- anyInt16le :: ParserT st e Int16
- anyInt16be :: ParserT st e Int16
- anyInt32le :: ParserT st e Int32
- anyInt32be :: ParserT st e Int32
- anyInt64le :: ParserT st e Int64
- anyInt64be :: ParserT st e Int64
- word8 :: Word8 -> ParserT st e ()
- withAnyWord8 :: (Word8 -> ParserT st e r) -> ParserT st e r
- withAnyWord16 :: (Word16 -> ParserT st e r) -> ParserT st e r
- withAnyWord32 :: (Word32 -> ParserT st e r) -> ParserT st e r
- withAnyWord64 :: (Word64 -> ParserT st e r) -> ParserT st e r
- withAnyInt8 :: (Int8 -> ParserT st e r) -> ParserT st e r
- withAnyInt16 :: (Int16 -> ParserT st e r) -> ParserT st e r
- withAnyInt32 :: (Int32 -> ParserT st e r) -> ParserT st e r
- withAnyInt64 :: (Int64 -> ParserT st e r) -> ParserT st e r
- withAnyWord :: (Word -> ParserT st e r) -> ParserT st e r
- withAnyInt :: (Int -> ParserT st e r) -> ParserT st e r
- anyWord8Unsafe :: ParserT st e Word8
- word8Unsafe :: Word8 -> ParserT st e ()
- word16Unsafe :: Word16 -> ParserT st e ()
- word32Unsafe :: Word32 -> ParserT st e ()
- word64Unsafe :: Word64 -> ParserT st e ()
- withAnySized# :: Int# -> (Addr# -> Int# -> a) -> (a -> ParserT st e r) -> ParserT st e r
- withAnySizedUnsafe# :: Int# -> (Addr# -> Int# -> a) -> (a -> ParserT st e r) -> ParserT st e r
- sizedUnsafe# :: Eq a => Int# -> (Addr# -> Int# -> a) -> a -> ParserT st e ()
Native byte order
Explicit endianness
Native endianness parsers are used where possible. For non-native endianness
parsers, we parse then use the corresponding byteSwapX
function. On x86, this
is inlined as a single BSWAP
instruction.
Value assertions
CPS parsers
withAnyWord16 :: (Word16 -> ParserT st e r) -> ParserT st e r Source #
Parse any Word16
(native byte order) (CPS).
withAnyWord32 :: (Word32 -> ParserT st e r) -> ParserT st e r Source #
Parse any Word32
(native byte order) (CPS).
withAnyWord64 :: (Word64 -> ParserT st e r) -> ParserT st e r Source #
Parse any Word64
(native byte order) (CPS).
withAnyInt16 :: (Int16 -> ParserT st e r) -> ParserT st e r Source #
Parse any Int16
(native byte order) (CPS).
withAnyInt32 :: (Int32 -> ParserT st e r) -> ParserT st e r Source #
Parse any Int32
(native byte order) (CPS).
withAnyInt64 :: (Int64 -> ParserT st e r) -> ParserT st e r Source #
Parse any Int64
(native byte order) (CPS).
withAnyWord :: (Word -> ParserT st e r) -> ParserT st e r Source #
Parse any Word
(native size) (CPS).
Unsafe
These unsafe parsers and helpers may be useful for efficient parsing in special situations e.g. you already know that the input has enough bytes. You should only use them if you can assert their necessary guarantees (see the individual function documentation).
anyWord8Unsafe :: ParserT st e Word8 Source #
Unsafely parse any Word8
, without asserting the input is non-empty.
The caller must guarantee that the input has enough bytes.
Value assertions
word8Unsafe :: Word8 -> ParserT st e () Source #
Unsafely read the next 1 byte and assert its value as a Word8
.
The caller must guarantee that the input has enough bytes.
word16Unsafe :: Word16 -> ParserT st e () Source #
Unsafely read the next 2 bytes and assert their value as a Word16
(native byte order).
The caller must guarantee that the input has enough bytes.
word32Unsafe :: Word32 -> ParserT st e () Source #
Unsafely read the next 4 bytes and assert their value as a Word32
.
(native byte order).
The caller must guarantee that the input has enough bytes.
word64Unsafe :: Word64 -> ParserT st e () Source #
Unsafely read the next 8 bytes and assert their value as a Word64
.
(native byte order).
The caller must guarantee that the input has enough bytes.
Helper definitions
withAnySized# :: Int# -> (Addr# -> Int# -> a) -> (a -> ParserT st e r) -> ParserT st e r Source #
Helper for defining CPS parsers for types of a constant byte size (i.e. machine integers).
Call this with an indexXYZOffAddr
primop (e.g.
indexWord8OffAddr
) and the size in bytes of the type you're
parsing.
withAnySizedUnsafe# :: Int# -> (Addr# -> Int# -> a) -> (a -> ParserT st e r) -> ParserT st e r Source #
Unsafe helper for defining CPS parsers for types of a constant byte size (i.e. machine integers).
Is really just syntactic sugar for applying the given parser and shifting the buffer along.
The caller must guarantee that the input has enough bytes.
sizedUnsafe# :: Eq a => Int# -> (Addr# -> Int# -> a) -> a -> ParserT st e () Source #
Unsafe helper for defining parsers for types of a constant byte size (i.e. machine integers) which assert the parsed value's... value.
Call this with an indexXYZOffAddr
primop (e.g.
indexWord8OffAddr
), the size in bytes of the type you're parsing,
and the expected value to test the parsed value against.
The caller must guarantee that the input has enough bytes.