| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Type.BitRecords.Builder.BitBuffer
- type BitStringMaxLength = 64
- type family ModuloBitStringMaxLength (len :: Nat) :: Nat where ...
- bitStringMaxLength :: Num a => a
- bitStringMaxLengthBytes :: Word64
- data BitString
- bitStringContent :: BitString -> Word64
- bitStringLength :: BitString -> Int
- isBitStringEmpty :: BitString -> Bool
- bitStringSpaceLeft :: BitString -> Int
- bitString :: Int -> Word64 -> BitString
- emptyBitString :: BitString
- bitStringProxyLength :: KnownChunkSize n => Proxy n -> Word64 -> BitString
- data BitStringBuilderChunk
- bitStringBuilderChunkContent :: BitStringBuilderChunk -> Word64
- bitStringBuilderChunkLength :: BitStringBuilderChunk -> Int
- isBitStringBuilderChunkEmpty :: BitStringBuilderChunk -> Bool
- bitStringBuilderChunkSpaceLeft :: BitStringBuilderChunk -> Int
- bitStringBuilderChunk :: Word64 -> Int -> BitStringBuilderChunk
- emptyBitStringBuilderChunk :: BitStringBuilderChunk
- bufferBits :: BitString -> BitStringBuilderChunk -> (BitString, BitStringBuilderChunk)
- type family KnownChunkSize (s :: Nat) :: Constraint where ...
Documentation
type BitStringMaxLength = 64 Source #
The maximum number of bits a BitBuffer can hold.
type family ModuloBitStringMaxLength (len :: Nat) :: Nat where ... Source #
Calculate the modulus of a number and the BitStringMaxLength.
Equations
| ModuloBitStringMaxLength len = len `RemPow2` 6 |
bitStringMaxLength :: Num a => a Source #
The maximum number of bits a BitBuffer can hold.
bitStringMaxLengthBytes :: Word64 Source #
The maximum number of bytes a BitBuffer can hold.
A string of bits with a given length (but always <= .
The number of bits must be smaller that bitStringMaxLengthbitStringMaxLength.
Instances
bitStringContent :: BitString -> Word64 Source #
bitStringLength :: BitString -> Int Source #
isBitStringEmpty :: BitString -> Bool Source #
bitStringSpaceLeft :: BitString -> Int Source #
bitString :: Int -> Word64 -> BitString Source #
Create a BitString containing len bits from LSB to MSB, properly
masked, such that only len least significant bits are kept..
emptyBitString :: BitString Source #
Create an empty BitString.
bitStringProxyLength :: KnownChunkSize n => Proxy n -> Word64 -> BitString Source #
Create a BitStringBuilderChunk with a length given by a Proxy to a type level
Nat.
data BitStringBuilderChunk Source #
A buffer for 64 bits, such that the bits are written MSB to LSB.
type TwoFields = "f0" @: Field m .+. "f1" @: Field n
Writes:
MSB LSB
Bit: |k .. k-(m+1)|k-m .. k-(m+n+1)|k-(m+n) .. 0|
Value: |------f0------|--------f1--------|XXXXXXXXXXXXXX|
Where k is the current bit offset.
The input values are expected to be in the order of the fields, i.e.:
runHoley $ bitStringBuilderHoley (Proxy :: Proxy TwoFields) 1 2
Will result in:
MSB LSB
Bit: |k .. k-(m+1)|k-m .. k-(m+n+1)| k-(m+n) .. 0|
Value: |0 .. 1|0 .. 10| X .. X|
bitStringBuilderChunk :: Word64 -> Int -> BitStringBuilderChunk Source #
Create a BitStringBuilderChunk containing len bits from LSB to MSB, properly
masked, such that only len least significant bits are kept..
emptyBitStringBuilderChunk :: BitStringBuilderChunk Source #
Create an empty BitStringBuilderChunk.
Arguments
| :: BitString | The value to write (in the lower |
| -> BitStringBuilderChunk | The input to write to |
| -> (BitString, BitStringBuilderChunk) | The remaining bits that did not fit in the buffer and the output buffer. |
Copy bits starting at a specific offset from one a the the other.
Set bits starting from the most significant bit to the least.
For example writeBits m 1 <> writeBits n 2 would result in:
MSB LSB
Bit: |k .. k-(m+1)|k-m .. k-(m+n+1)| k-(m+n) .. 0|
Value: |0 .. 1|0 .. 10| ... |
-> -> -> (direction of writing)
type family KnownChunkSize (s :: Nat) :: Constraint where ... Source #
Equations
| KnownChunkSize size = (KnownNat size, size <= BitStringMaxLength) |