Copyright | (C) 2013-2016 University of Twente 2016-2017 Myrtle Software Ltd 2021-2023 QBayLogic B.V. 2022 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Extensions |
|
Synopsis
- class KnownNat (BitSize a) => BitPack a where
- packXWith :: KnownNat n => (a -> BitVector n) -> a -> BitVector n
- xToBV :: KnownNat n => BitVector n -> BitVector n
- 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
- packFloat# :: Float -> BitVector 32
- unpackFloat# :: BitVector 32 -> Float
- packDouble# :: Double -> BitVector 64
- unpackDouble# :: BitVector 64 -> Double
- class GBitPack f where
- type GFieldSize f :: Nat
- type GConstructorCount f :: Nat
- gPackFields :: Int -> f a -> (Int, BitVector (GFieldSize f))
- gUnpack :: Int -> Int -> BitVector (GFieldSize f) -> f a
- boolToBV :: KnownNat n => Bool -> BitVector (n + 1)
- boolToBit :: Bool -> Bit
- bitToBool :: Bit -> Bool
Documentation
>>>
:m -Prelude
>>>
:set -XDataKinds
>>>
import Clash.Prelude
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.
It is not possible to give data a custom bit representation by providing a
BitPack
instance. A BitPack
instance allows no creativity and should
always accurately reflect the bit representation of the data in HDL. You
should always derive (
unless you use a custom data
representation, in which case you should use
Generic
, BitPack)deriveBitPack
. Custom
encodings can be created with Clash.Annotations.BitRepresentation and
Clash.Annotations.BitRepresentation.Deriving.
If the BitPack
instance does not accurately match the bit representation of
the data in HDL, Clash designs will exhibit incorrect behavior in various
places.
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
NB: 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
packFloat# :: Float -> BitVector 32 Source #
unpackFloat# :: BitVector 32 -> Float Source #
packDouble# :: Double -> BitVector 64 Source #
unpackDouble# :: BitVector 64 -> Double Source #
class GBitPack f where Source #
type GFieldSize f :: Nat Source #
Size of fields. If multiple constructors exist, this is the maximum of the sum of each of the constructors fields.
type GConstructorCount f :: Nat Source #
Number of constructors this type has. Indirectly indicates how many bits are needed to represent the constructor.
:: Int | Current constructor |
-> f a | Data to pack |
-> (Int, BitVector (GFieldSize f)) | (Constructor number, Packed fields) |
Pack fields of a type. Caller should pack and prepend the constructor bits.
:: Int | Construct with constructor n |
-> Int | Current constructor |
-> BitVector (GFieldSize f) | BitVector containing fields |
-> f a | Unpacked result |
Unpack whole type.