clash-prelude-1.7.0: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
2016-2017 Myrtle Software Ltd
2021-2023 QBayLogic B.V.
2022 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • Cpp
  • UndecidableInstances
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • BangPatterns
  • TypeFamilies
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • FlexibleContexts
  • MagicHash
  • KindSignatures
  • PostfixOperators
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Class.BitPack.Internal

Description

 
Synopsis

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 (Generic, BitPack) unless you use a custom data representation, in which case you should use 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).

Minimal complete definition

Nothing

Associated Types

type BitSize a :: Nat Source #

Number of Bits 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)

Methods

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

default unpack :: (Generic a, GBitPack (Rep a), KnownNat constrSize, KnownNat fieldSize, constrSize ~ CLog 2 (GConstructorCount (Rep a)), fieldSize ~ GFieldSize (Rep a), (constrSize + fieldSize) ~ BitSize a) => BitVector (BitSize a) -> a Source #

Instances

Instances details
BitPack Bool Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Bool :: Nat Source #

BitPack Double Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Double :: Nat Source #

BitPack Float Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Float :: Nat Source #

BitPack Int Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Int :: Nat Source #

BitPack Int8 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Int8 :: Nat Source #

BitPack Int16 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Int16 :: Nat Source #

BitPack Int32 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Int32 :: Nat Source #

BitPack Int64 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Int64 :: Nat Source #

BitPack Ordering Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Ordering :: Nat Source #

BitPack Word Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Word :: Nat Source #

BitPack Word8 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Word8 :: Nat Source #

BitPack Word16 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Word16 :: Nat Source #

BitPack Word32 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Word32 :: Nat Source #

BitPack Word64 Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Word64 :: Nat Source #

BitPack () Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize () :: Nat Source #

Methods

pack :: () -> BitVector (BitSize ()) Source #

unpack :: BitVector (BitSize ()) -> () Source #

BitPack CUShort Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize CUShort :: Nat Source #

BitPack Half Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Half :: Nat Source #

BitPack Bit Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Bit :: Nat Source #

BitPack a => BitPack (Maybe a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Maybe a) :: Nat Source #

BitPack a => BitPack (Complex a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Complex a) :: Nat Source #

BitPack a => BitPack (Identity a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Identity a) :: Nat Source #

BitPack a => BitPack (Down a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Down a) :: Nat Source #

KnownNat n => BitPack (BitVector n) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (BitVector n) :: Nat Source #

(KnownNat n, 1 <= n) => BitPack (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Associated Types

type BitSize (Index n) :: Nat Source #

KnownNat n => BitPack (Unsigned n) Source # 
Instance details

Defined in Clash.Sized.Internal.Unsigned

Associated Types

type BitSize (Unsigned n) :: Nat Source #

KnownNat n => BitPack (Signed n) Source # 
Instance details

Defined in Clash.Sized.Internal.Signed

Associated Types

type BitSize (Signed n) :: Nat Source #

BitPack a => BitPack (Zeroing a) Source # 
Instance details

Defined in Clash.Num.Zeroing

Associated Types

type BitSize (Zeroing a) :: Nat Source #

BitPack a => BitPack (Wrapping a) Source # 
Instance details

Defined in Clash.Num.Wrapping

Associated Types

type BitSize (Wrapping a) :: Nat Source #

BitPack a => BitPack (Saturating a) Source # 
Instance details

Defined in Clash.Num.Saturating

Associated Types

type BitSize (Saturating a) :: Nat Source #

(BitPack a, KnownNat (BitSize a + 1)) => BitPack (Overflowing a) Source # 
Instance details

Defined in Clash.Num.Overflowing

Associated Types

type BitSize (Overflowing a) :: Nat Source #

BitPack a => BitPack (Erroring a) Source # 
Instance details

Defined in Clash.Num.Erroring

Associated Types

type BitSize (Erroring a) :: Nat Source #

(BitPack a, BitPack b) => BitPack (Either a b) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Either a b) :: Nat Source #

Methods

pack :: Either a b -> BitVector (BitSize (Either a b)) Source #

unpack :: BitVector (BitSize (Either a b)) -> Either a b Source #

(BitPack a, BitPack b) => BitPack (a, b) Source #

N.B.: The documentation only shows instances up to 3-tuples. By default, instances up to and including 12-tuples will exist. If the flag large-tuples is set instances up to the GHC imposed limit will exist. The GHC imposed limit is either 62 or 64 depending on the GHC version.

Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (a, b) :: Nat Source #

Methods

pack :: (a, b) -> BitVector (BitSize (a, b)) Source #

unpack :: BitVector (BitSize (a, b)) -> (a, b) Source #

(KnownNat n, BitPack a) => BitPack (Vec n a) Source # 
Instance details

Defined in Clash.Sized.Vector

Associated Types

type BitSize (Vec n a) :: Nat Source #

Methods

pack :: Vec n a -> BitVector (BitSize (Vec n a)) Source #

unpack :: BitVector (BitSize (Vec n a)) -> Vec n a Source #

(KnownNat d, BitPack a) => BitPack (RTree d a) Source # 
Instance details

Defined in Clash.Sized.RTree

Associated Types

type BitSize (RTree d a) :: Nat Source #

Methods

pack :: RTree d a -> BitVector (BitSize (RTree d a)) Source #

unpack :: BitVector (BitSize (RTree d a)) -> RTree d a Source #

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3), KnownNat (BitSize (a2, a3))) => BitPack (a1, a2, a3) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (a1, a2, a3) :: Nat Source #

Methods

pack :: (a1, a2, a3) -> BitVector (BitSize (a1, a2, a3)) Source #

unpack :: BitVector (BitSize (a1, a2, a3)) -> (a1, a2, a3) Source #

BitPack a => BitPack (Const a b) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Const a b) :: Nat Source #

Methods

pack :: Const a b -> BitVector (BitSize (Const a b)) Source #

unpack :: BitVector (BitSize (Const a b)) -> Const a b Source #

(BitPack (rep (int + frac)), KnownNat (BitSize (rep (int + frac)))) => BitPack (Fixed rep int frac) Source # 
Instance details

Defined in Clash.Sized.Fixed

Associated Types

type BitSize (Fixed rep int frac) :: Nat Source #

Methods

pack :: Fixed rep int frac -> BitVector (BitSize (Fixed rep int frac)) Source #

unpack :: BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac Source #

(BitPack (f a), BitPack (g a)) => BitPack (Product f g a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Product f g a) :: Nat Source #

Methods

pack :: Product f g a -> BitVector (BitSize (Product f g a)) Source #

unpack :: BitVector (BitSize (Product f g a)) -> Product f g a Source #

(BitPack (f a), BitPack (g a)) => BitPack (Sum f g a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Sum f g a) :: Nat Source #

Methods

pack :: Sum f g a -> BitVector (BitSize (Sum f g a)) Source #

unpack :: BitVector (BitSize (Sum f g a)) -> Sum f g a Source #

BitPack (f (g a)) => BitPack (Compose f g a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (Compose f g a) :: Nat Source #

Methods

pack :: Compose f g a -> BitVector (BitSize (Compose f g a)) Source #

unpack :: BitVector (BitSize (Compose f g a)) -> Compose f g a Source #

packXWith :: KnownNat n => (a -> BitVector n) -> a -> BitVector n Source #

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

class GBitPack f where Source #

Associated Types

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.

Methods

gPackFields Source #

Arguments

:: 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.

gUnpack Source #

Arguments

:: Int

Construct with constructor n

-> Int

Current constructor

-> BitVector (GFieldSize f)

BitVector containing fields

-> f a

Unpacked result

Unpack whole type.

Instances

Instances details
GBitPack (U1 :: Type -> Type) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type GFieldSize U1 :: Nat Source #

type GConstructorCount U1 :: Nat Source #

BitPack c => GBitPack (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type GFieldSize (K1 i c) :: Nat Source #

type GConstructorCount (K1 i c) :: Nat Source #

Methods

gPackFields :: Int -> K1 i c a -> (Int, BitVector (GFieldSize (K1 i c))) Source #

gUnpack :: Int -> Int -> BitVector (GFieldSize (K1 i c)) -> K1 i c a Source #

(KnownNat (GFieldSize g), KnownNat (GFieldSize f), KnownNat (GConstructorCount f), GBitPack f, GBitPack g) => GBitPack (f :+: g) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type GFieldSize (f :+: g) :: Nat Source #

type GConstructorCount (f :+: g) :: Nat Source #

Methods

gPackFields :: Int -> (f :+: g) a -> (Int, BitVector (GFieldSize (f :+: g))) Source #

gUnpack :: Int -> Int -> BitVector (GFieldSize (f :+: g)) -> (f :+: g) a Source #

(KnownNat (GFieldSize g), KnownNat (GFieldSize f), GBitPack f, GBitPack g) => GBitPack (f :*: g) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type GFieldSize (f :*: g) :: Nat Source #

type GConstructorCount (f :*: g) :: Nat Source #

Methods

gPackFields :: Int -> (f :*: g) a -> (Int, BitVector (GFieldSize (f :*: g))) Source #

gUnpack :: Int -> Int -> BitVector (GFieldSize (f :*: g)) -> (f :*: g) a Source #

GBitPack a => GBitPack (M1 m d a) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type GFieldSize (M1 m d a) :: Nat Source #

type GConstructorCount (M1 m d a) :: Nat Source #

Methods

gPackFields :: Int -> M1 m d a a0 -> (Int, BitVector (GFieldSize (M1 m d a))) Source #

gUnpack :: Int -> Int -> BitVector (GFieldSize (M1 m d a)) -> M1 m d a a0 Source #

boolToBV :: KnownNat n => Bool -> BitVector (n + 1) Source #

Zero-extend a Boolean value to a BitVector of the appropriate size.

>>> boolToBV True :: BitVector 6
0b00_0001
>>> boolToBV False :: BitVector 6
0b00_0000

boolToBit :: Bool -> Bit Source #

Convert a Bool to a Bit

bitToBool :: Bit -> Bool Source #

Convert a Bit to a Bool