flat-0.6: Principled and efficient bit-oriented binary serialization.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Flat.Decoder.Prim

Description

Strict Decoder Primitives

Synopsis

Documentation

dBool :: Get Bool Source #

Decode a boolean

dWord8 :: Get Word8 Source #

Return the 8 most significant bits (same as dBE8)

dBE8 :: Get Word8 Source #

Return the 8 most significant bits

dBE16 :: Get Word16 Source #

Return the 16 most significant bits

dBE32 :: Get Word32 Source #

Return the 32 most significant bits

dBE64 :: Get Word64 Source #

Return the 64 most significant bits

dBEBits8 :: Int -> Get Word8 Source #

Return the n most significant bits (up to maximum of 8)

The bits are returned right shifted:

>>> unflatWith (dBEBits8 3) [0b11100001::Word8] == Right 0b00000111
True
>>> unflatWith (dBEBits8 9) [0b11100001::Word8,0b11111111]
Left (BadOp "read8: cannot read 9 bits")

dBEBits16 :: Int -> Get Word16 Source #

Return the n most significant bits (up to maximum of 16)

The bits are returned right shifted:

>>> pPrint . asBits <$> unflatWith (dBEBits16 11) [0b10110111::Word8,0b11100001]
Right 00000101 10111111

If more than 16 bits are requested, only the last 16 are returned:

>>> pPrint . asBits <$> unflatWith (dBEBits16 19) [0b00000000::Word8,0b11111111,0b11100001]
Right 00000111 11111111

dBEBits32 :: Int -> Get Word32 Source #

Return the n most significant bits (up to maximum of 32) The bits are returned right shifted.

dBEBits64 :: Int -> Get Word64 Source #

Return the n most significant bits (up to maximum of 64) The bits are returned right shifted.

dropBits :: Int -> Get () Source #

Drop the specified number of bits

dFloat :: Get Float Source #

Decode a Float

dDouble :: Get Double Source #

Decode a Double

getChunksInfo :: Get (Ptr Word8, [Int]) Source #

Decode an Array (a list of chunks up to 255 bytes long) returning the pointer to the first data byte and a list of chunk sizes

dByteString_ :: Get ByteString Source #

Decode a ByteString

dLazyByteString_ :: Get ByteString Source #

Decode a Lazy ByteString

dByteArray_ :: Get (ByteArray, Int) Source #

Decode a ByteArray and its length

data ConsState Source #

A special state, optimised for constructor decoding.

It consists of:

  • The bits to parse, the top bit being the first to parse (could use a Word16 instead, no difference in performance)
  • The number of decoded bits

Supports up to 512 constructors (9 bits).

Constructors

ConsState !Word !Int 

consOpen :: Get ConsState Source #

Switch to constructor decoding {-# INLINE consOpen #-}

consClose :: Int -> Get () Source #

Switch back to normal decoding {-# NOINLINE consClose #-}

consBool :: ConsState -> (ConsState, Bool) Source #

Decode a single bit

consBits :: ConsState -> Int -> (ConsState, Word) Source #

Decode from 1 to 3 bits

It could read more bits that are available, but it doesn't matter, errors will be checked in consClose.

sizeOf :: Get a -> Get Int Source #

Given a value's decoder, returns the size in bits of the encoded value

Since: 0.6

binOf :: Get a -> Get (ByteString, Int) Source #

Given a value's decoder, returns the value's bit encoding.

The encoding starts at the returned bit position in the return bytestring's first byte and ends in an unspecified bit position in its final byte

Since: 0.6