| Copyright | (c) Benjamin Selfridge 2018 Galois Inc. |
|---|---|
| License | BSD3 |
| Maintainer | benselfridge@galois.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.BitVector.Sized.BitLayout
Description
- data Chunk (w :: Nat) :: * where
- chunk :: KnownNat w => Int -> Chunk w
- data BitLayout (t :: Nat) (s :: Nat) :: *
- empty :: KnownNat t => BitLayout t 0
- (<:) :: Chunk r -> BitLayout t s -> BitLayout t (r + s)
- inject :: BitLayout t s -> BitVector t -> BitVector s -> BitVector t
- extract :: BitLayout t s -> BitVector t -> BitVector s
- layoutLens :: BitLayout t s -> Simple Lens (BitVector t) (BitVector s)
Chunk
data Chunk (w :: Nat) :: * where Source #
Chunk type, parameterized by chunk width. The internal Int is the
position of the least significant bit of the chunk, and the type-level nat w is
the width of the chunk.
>>>chunk 2 :: Chunk 5Chunk 5 2
Intuitively, the above chunk index captures the notion of embedding a
BitVector 5 (bit vector of width 5) into a larger BitVector at index 2,
preserving the order of the input bits. So an 5-bit input like 10011 would map
to some larger bit vector containing the input starting at position 2, like
000001001100.
chunk :: KnownNat w => Int -> Chunk w Source #
Construct a Chunk in a context where the chunk width is known at compile time.
BitLayout
data BitLayout (t :: Nat) (s :: Nat) :: * Source #
BitLayout type, parameterized by target width and source width. t is the
target width, s is the source width. s should always be less than or equal to
t.
To construct a BitLayout, use the empty constructor and the <: operator,
like so:
>>>empty :: BitLayout 32 0BitLayout 32 0 (fromList [])>>>let layout = (chunk 25 :: Chunk 7) <: (chunk 7 :: Chunk 5) <: (empty :: BitLayout 32 0)>>>layoutBitLayout 32 12 (fromList [Chunk 5 7,Chunk 7 25])>>>:type itit :: BitLayout 32 12
In the above example bitLayout defines a chunk-by-chunk mapping from a bit
vector of width 12 to one of width 32. We imagine the input vector of width 12
listed like so:
0bAXXXXXBCXXXD
|-----||---|
7 5
Here, bits A, B, C, and D are just labeled as such to illustrate their
place after the mapping. The BitLayout 32 12 defined above as the layout
variable would map that 12-bit vector to the following 32-bit vector:
(Bit 25) (Bit 5)
| |
| |
v v
0bAXXXXXB0000000000000CXXXD0000000
|-----| |---|
7 5
To use a BitLayout to achieve a bidirectional mapping like the one described
above, you can either use the Lens interface or the functions inject and
extract, which give an explicit setter and getter, respectively.
Example use of inject/extract:
>>>let bl = (chunk 25 :: Chunk 7) <: (chunk 7 :: Chunk 5) <: (empty :: BitLayout 32 0)>>>let sVec = bitVector 0b111111100001 :: BitVector 12>>>sVec0xfe1>>>inject bl (bitVector 0) (bitVector 0b111111100001)0xfe000080>>>extract bl $ inject bl (bitVector 0) (bitVector 0b111111100001)0xfe1
Arguments
| :: BitLayout t s | The layout |
| -> BitVector t | The larger vector to inject into |
| -> BitVector s | The smaller vector to be injected |
| -> BitVector t |
Use a BitLayout to inject a smaller vector into a larger one.
Use a BitLayout to extract a smaller vector from a larger one.