clash-prelude-0.10.11: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2013-2016, University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • MonoLocalBinds
  • TypeFamilies
  • ViewPatterns
  • DataKinds
  • FlexibleContexts
  • MagicHash
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces

CLaSH.Class.BitPack

Description

 

Synopsis

Documentation

class BitPack a where Source

Convert to and from a BitVector

Associated Types

type BitSize a :: Nat Source

Number of Bits needed to represents elements of type a

Methods

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

Convert element of type a to a BitVector

>>> pack (-5 :: Signed 6)
11_1011

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

Instances

BitPack Bool Source 
KnownNat n => BitPack (Index n) Source 
BitPack (BitVector n) Source 
KnownNat n => BitPack (Signed n) Source 
BitPack (Unsigned n) Source 
(KnownNat (BitSize b), BitPack a, BitPack b) => BitPack (a, b) Source 
(KnownNat n, KnownNat (BitSize a), BitPack a) => BitPack (Vec n a) Source 
(KnownNat (BitSize c), BitPack (a, b), BitPack c) => BitPack (a, b, c) Source 
BitPack (rep ((+) int frac)) => BitPack (Fixed rep int frac) Source 
(KnownNat (BitSize d), BitPack (a, b, c), BitPack d) => BitPack (a, b, c, d) Source 
(KnownNat (BitSize e), BitPack (a, b, c, d), BitPack e) => BitPack (a, b, c, d, e) Source 
(KnownNat (BitSize f), BitPack (a, b, c, d, e), BitPack f) => BitPack (a, b, c, d, e, f) Source 
(KnownNat (BitSize g), BitPack (a, b, c, d, e, f), BitPack g) => BitPack (a, b, c, d, e, f, g) Source 
(KnownNat (BitSize h), BitPack (a, b, c, d, e, f, g), BitPack h) => BitPack (a, b, c, d, e, f, g, h) 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

boolToBV :: (KnownNat n, KnownNat (n + 1)) => 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