Copyright | (C) 2013-2016 University of Twente 2016-2017 Myrtle Software Ltd 2021 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- class KnownNat (BitSize a) => BitPack a where
- isLike :: BitPack a => a -> a -> Bool
- bitCoerce :: (BitPack a, BitPack b, BitSize a ~ BitSize b) => a -> b
- bitCoerceMap :: forall a b. (BitPack a, BitPack b, BitSize a ~ BitSize b) => (a -> a) -> b -> b
- boolToBV :: KnownNat n => Bool -> BitVector (n + 1)
- boolToBit :: Bool -> Bit
- bitToBool :: Bit -> Bool
- packXWith :: KnownNat n => (a -> BitVector n) -> a -> BitVector n
- (!) :: (BitPack a, Enum i) => a -> i -> Bit
- slice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> a -> BitVector ((m + 1) - n)
- split :: (BitPack a, BitSize a ~ (m + n), KnownNat n) => a -> (BitVector m, BitVector n)
- replaceBit :: (BitPack a, Enum i) => i -> Bit -> a -> a
- setSlice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> BitVector ((m + 1) - n) -> a -> a
- msb :: BitPack a => a -> Bit
- lsb :: BitPack a => a -> Bit
- reduceAnd :: BitPack a => a -> Bit
- reduceOr :: BitPack a => a -> Bit
- reduceXor :: BitPack a => a -> Bit
Documentation
class KnownNat (BitSize a) => BitPack a where Source #
Convert data to/from a BitVector
. This allows functions to be defined
on the underlying representation of data, while exposing a nicer API using
pack
/ unpack
at the boundaries. For example:
f :: forall a b. (BitPack a, BitPack b) => a -> b f = unpack . go . pack where go :: BitVector (BitSize a) -> BitVector (BitSize b) go = _ -- A function on the underlying bit vector
A type should only implement this class if it has a statically known size,
as otherwise it is not possible to determine how many bits are needed to
represent values. This means that types such as [a]
cannot have BitPack
instances, as even if a
has a statically known size, the length of the
list cannot be known in advance.
Clash provides some generic functions on packable types in the prelude, such as indexing into packable stuctures (see Clash.Class.BitPack.BitIndex) and bitwise reduction of packable data (see Clash.Class.BitPack.BitReduction).
Nothing
type BitSize a :: Nat Source #
Number of Bit
s needed to represents elements
of type a
Can be derived using Generics
:
import Clash.Prelude import GHC.Generics data MyProductType = MyProductType { a :: Int, b :: Bool } deriving (Generic, BitPack)
type BitSize a = CLog 2 (GConstructorCount (Rep a)) + GFieldSize (Rep a)
pack :: a -> BitVector (BitSize a) Source #
Convert element of type a
to a BitVector
>>>
pack (-5 :: Signed 6)
0b11_1011
default pack :: (Generic a, GBitPack (Rep a), KnownNat (BitSize a), KnownNat constrSize, KnownNat fieldSize, constrSize ~ CLog 2 (GConstructorCount (Rep a)), fieldSize ~ GFieldSize (Rep a), (constrSize + fieldSize) ~ BitSize a) => a -> BitVector (BitSize a) Source #
unpack :: BitVector (BitSize a) -> a Source #
Convert a BitVector
to an element of type a
>>>
pack (-5 :: Signed 6)
0b11_1011>>>
let x = pack (-5 :: Signed 6)
>>>
unpack x :: Unsigned 6
59>>>
pack (59 :: Unsigned 6)
0b11_1011
Instances
isLike :: BitPack a => a -> a -> Bool Source #
Pack both arguments to a BitVector
and use
isLike#
to compare them. This is a more
lentiant comparison than (==)
, behaving more like (but not necessarily
exactly the same as) std_match
in VHDL or casez
in Verilog.
Unlike (==)
, isLike is not symmetric. The reason for this is that a
defined bit is said to be like an undefined bit, but not vice-versa:
>>>
isLike (12 :: Signed 8) undefined
True>>>
isLike undefined (12 :: Signed 8)
False
However, it is still trivially reflexive and transitive:
>>>
:set -XTemplateHaskell
>>>
let x1 = $(bLit "0010")
>>>
let x2 = $(bLit "0.10")
>>>
let x3 = $(bLit "0.1.")
>>>
isLike x1 x1
True>>>
isLike x1 x2
True>>>
isLike x2 x3
True>>>
isLike x1 x3
True
N.B.: Not synthesizable
bitCoerce :: (BitPack a, BitPack b, BitSize a ~ BitSize b) => a -> b Source #
Coerce a value from one type to another through its bit representation.
>>>
pack (-5 :: Signed 6)
0b11_1011>>>
bitCoerce (-5 :: Signed 6) :: Unsigned 6
59>>>
pack (59 :: Unsigned 6)
0b11_1011
bitCoerceMap :: forall a b. (BitPack a, BitPack b, BitSize a ~ BitSize b) => (a -> a) -> b -> b Source #
Map a value by first coercing to another type through its bit representation.
>>>
pack (-5 :: Signed 32)
0b1111_1111_1111_1111_1111_1111_1111_1011>>>
bitCoerceMap @(Vec 4 (BitVector 8)) (replace 1 0) (-5 :: Signed 32)
-16711685>>>
pack (-16711685 :: Signed 32)
0b1111_1111_0000_0000_1111_1111_1111_1011
Bit Indexing
(!) :: (BitPack a, Enum i) => a -> i -> Bit Source #
Get the bit at the specified bit index.
NB: Bit indices are DESCENDING.
>>>
pack (7 :: Unsigned 6)
0b00_0111>>>
(7 :: Unsigned 6) ! 1
1>>>
(7 :: Unsigned 6) ! 5
0>>>
(7 :: Unsigned 6) ! 6
*** Exception: (!): 6 is out of range [5..0] ...
slice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> a -> BitVector ((m + 1) - n) Source #
Get a slice between bit index m
and and bit index n
.
NB: Bit indices are DESCENDING.
>>>
pack (7 :: Unsigned 6)
0b00_0111>>>
slice d4 d2 (7 :: Unsigned 6)
0b001>>>
slice d6 d4 (7 :: Unsigned 6)
<interactive>:... • Couldn't match type ‘7 + i0’ with ‘6’ arising from a use of ‘slice’ The type variable ‘i0’ is ambiguous • In the expression: slice d6 d4 (7 :: Unsigned 6) In an equation for ‘it’: it = slice d6 d4 (7 :: Unsigned 6)
split :: (BitPack a, BitSize a ~ (m + n), KnownNat n) => a -> (BitVector m, BitVector n) Source #
Split a value of a bit size m + n
into a tuple of values with size m
and size n
.
>>>
pack (7 :: Unsigned 6)
0b00_0111>>>
split (7 :: Unsigned 6) :: (BitVector 2, BitVector 4)
(0b00,0b0111)
replaceBit :: (BitPack a, Enum i) => i -> Bit -> a -> a Source #
Set the bit at the specified index
NB: Bit indices are DESCENDING.
>>>
pack (-5 :: Signed 6)
0b11_1011>>>
replaceBit 4 0 (-5 :: Signed 6)
-21>>>
pack (-21 :: Signed 6)
0b10_1011>>>
replaceBit 5 0 (-5 :: Signed 6)
27>>>
pack (27 :: Signed 6)
0b01_1011>>>
replaceBit 6 0 (-5 :: Signed 6)
*** Exception: replaceBit: 6 is out of range [5..0] ...
setSlice :: (BitPack a, BitSize a ~ ((m + 1) + i)) => SNat m -> SNat n -> BitVector ((m + 1) - n) -> a -> a Source #
Set the bits between bit index m
and bit index n
.
NB: Bit indices are DESCENDING.
>>>
pack (-5 :: Signed 6)
0b11_1011>>>
setSlice d4 d3 0 (-5 :: Signed 6)
-29>>>
pack (-29 :: Signed 6)
0b10_0011>>>
setSlice d6 d5 0 (-5 :: Signed 6)
<interactive>:... • Couldn't match type ‘7 + i0’ with ‘6’ arising from a use of ‘setSlice’ The type variable ‘i0’ is ambiguous • In the expression: setSlice d6 d5 0 (- 5 :: Signed 6) In an equation for ‘it’: it = setSlice d6 d5 0 (- 5 :: Signed 6)
msb :: BitPack a => a -> Bit Source #
Get the most significant bit.
>>>
pack (-4 :: Signed 6)
0b11_1100>>>
msb (-4 :: Signed 6)
1>>>
pack (4 :: Signed 6)
0b00_0100>>>
msb (4 :: Signed 6)
0
lsb :: BitPack a => a -> Bit Source #
Get the least significant bit.
>>>
pack (-9 :: Signed 6)
0b11_0111>>>
lsb (-9 :: Signed 6)
1>>>
pack (-8 :: Signed 6)
0b11_1000>>>
lsb (-8 :: Signed 6)
0
Bit Reduction
reduceAnd :: BitPack a => a -> Bit Source #
Are all bits set to '1'?
>>>
pack (-2 :: Signed 6)
0b11_1110>>>
reduceAnd (-2 :: Signed 6)
0>>>
pack (-1 :: Signed 6)
0b11_1111>>>
reduceAnd (-1 :: Signed 6)
1
Zero width types will evaluate to '1':
>>>
reduceAnd (0 :: Unsigned 0)
1
reduceOr :: BitPack a => a -> Bit Source #
Is there at least one bit set to '1'?
>>>
pack (5 :: Signed 6)
0b00_0101>>>
reduceOr (5 :: Signed 6)
1>>>
pack (0 :: Signed 6)
0b00_0000>>>
reduceOr (0 :: Signed 6)
0
Zero width types will evaluate to '0':
>>>
reduceOr (0 :: Unsigned 0)
0
reduceXor :: BitPack a => a -> Bit Source #
Is the number of bits set to '1' uneven?
>>>
pack (5 :: Signed 6)
0b00_0101>>>
reduceXor (5 :: Signed 6)
0>>>
pack (28 :: Signed 6)
0b01_1100>>>
reduceXor (28 :: Signed 6)
1>>>
pack (-5 :: Signed 6)
0b11_1011>>>
reduceXor (-5 :: Signed 6)
1
Zero width types will evaluate to '0':
>>>
reduceXor (0 :: Unsigned 0)
0