clash-prelude-1.3.0: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2013-2016 University of Twente
2016-2017 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.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
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Class.BitPack

Contents

Description

 
Synopsis

Documentation

class KnownNat (BitSize a) => BitPack a where Source #

Convert to and from a BitVector

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)
11_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)
11_1011
>>> let x = pack (-5 :: Signed 6)
>>> unpack x :: Unsigned 6
59
>>> pack (59 :: Unsigned 6)
11_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

Associated Types

type BitSize Bool :: Nat Source #

BitPack Double Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Double :: Nat Source #

BitPack Float Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Float :: Nat Source #

BitPack Int Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Int :: Nat Source #

BitPack Int8 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Int8 :: Nat Source #

BitPack Int16 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Int16 :: Nat Source #

BitPack Int32 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Int32 :: Nat Source #

BitPack Int64 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Int64 :: Nat Source #

BitPack Word Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Word :: Nat Source #

BitPack Word8 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Word8 :: Nat Source #

BitPack Word16 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Word16 :: Nat Source #

BitPack Word32 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Word32 :: Nat Source #

BitPack Word64 Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Word64 :: Nat Source #

BitPack () Source # 
Instance details

Defined in Clash.Class.BitPack

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

Associated Types

type BitSize CUShort :: Nat Source #

BitPack Half Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Half :: Nat Source #

BitPack Bit Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Bit :: Nat Source #

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

Defined in Clash.Class.BitPack

Associated Types

type BitSize (Maybe a) :: Nat Source #

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

Defined in Clash.Class.BitPack

Associated Types

type BitSize (Complex a) :: Nat Source #

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

Defined in Clash.Class.BitPack

Associated Types

type BitSize (Down a) :: Nat Source #

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

Defined in Clash.Class.BitPack

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 b) => BitPack (Either a b) Source # 
Instance details

Defined in Clash.Class.BitPack

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 # 
Instance details

Defined in Clash.Class.BitPack

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

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 (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 a1, KnownNat (BitSize a1), BitPack (a2, a3, a4), KnownNat (BitSize (a2, a3, a4))) => BitPack (a1, a2, a3, a4) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

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

Methods

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

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

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

Defined in Clash.Class.BitPack

Associated Types

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

Methods

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

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

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

Defined in Clash.Class.BitPack

Associated Types

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

Methods

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

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

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3, a4, a5, a6, a7), KnownNat (BitSize (a2, a3, a4, a5, a6, a7))) => BitPack (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (a1, a2, a3, a4, a5, a6, a7) :: Nat Source #

Methods

pack :: (a1, a2, a3, a4, a5, a6, a7) -> BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7)) Source #

unpack :: BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7)) -> (a1, a2, a3, a4, a5, a6, a7) Source #

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3, a4, a5, a6, a7, a8), KnownNat (BitSize (a2, a3, a4, a5, a6, a7, a8))) => BitPack (a1, a2, a3, a4, a5, a6, a7, a8) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (a1, a2, a3, a4, a5, a6, a7, a8) :: Nat Source #

Methods

pack :: (a1, a2, a3, a4, a5, a6, a7, a8) -> BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8)) Source #

unpack :: BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8)) -> (a1, a2, a3, a4, a5, a6, a7, a8) Source #

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3, a4, a5, a6, a7, a8, a9), KnownNat (BitSize (a2, a3, a4, a5, a6, a7, a8, a9))) => BitPack (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9) :: Nat Source #

Methods

pack :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9)) Source #

unpack :: BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source #

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3, a4, a5, a6, a7, a8, a9, a10), KnownNat (BitSize (a2, a3, a4, a5, a6, a7, a8, a9, a10))) => BitPack (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) :: Nat Source #

Methods

pack :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10)) Source #

unpack :: BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source #

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3, a4, a5, a6, a7, a8, a9, a10, a11), KnownNat (BitSize (a2, a3, a4, a5, a6, a7, a8, a9, a10, a11))) => BitPack (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) :: Nat Source #

Methods

pack :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11)) Source #

unpack :: BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source #

(BitPack a1, KnownNat (BitSize a1), BitPack (a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12), KnownNat (BitSize (a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12))) => BitPack (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) :: Nat Source #

Methods

pack :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12)) Source #

unpack :: BitVector (BitSize (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source #

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)
11_1011
>>> bitCoerce (-5 :: Signed 6) :: Unsigned 6
59
>>> pack (59 :: Unsigned 6)
11_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)
1111_1111_1111_1111_1111_1111_1111_1011
>>> bitCoerceMap @(Vec 4 (BitVector 8)) (replace 1 0) (-5 :: Signed 32)
-16711685
>>> pack (-16711685 :: Signed 32)
1111_1111_0000_0000_1111_1111_1111_1011

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

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

>>> boolToBV True :: BitVector 6
00_0001
>>> boolToBV False :: BitVector 6
00_0000

boolToBit :: Bool -> Bit Source #

Convert a Bool to a Bit

bitToBool :: Bit -> Bool Source #

Convert a Bool to a Bit

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

Internals

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

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

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

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

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

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 #