clash-prelude-1.4.2: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • 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.Prelude.BitIndex

Description

 
Synopsis

Documentation

>>> :set -XDataKinds
>>> import Clash.Prelude

(!) :: (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)
00_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)
00_0111
>>> slice d4 d2 (7 :: Unsigned 6)
001
>>> 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)
00_0111
>>> split (7 :: Unsigned 6) :: (BitVector 2, BitVector 4)
(00,0111)

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)
11_1011
>>> replaceBit 4 0 (-5 :: Signed 6)
-21
>>> pack (-21 :: Signed 6)
10_1011
>>> replaceBit 5 0 (-5 :: Signed 6)
27
>>> pack (27 :: Signed 6)
01_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)
11_1011
>>> setSlice d4 d3 0 (-5 :: Signed 6)
-29
>>> pack (-29 :: Signed 6)
10_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)
11_1100
>>> msb (-4 :: Signed 6)
1
>>> pack (4 :: Signed 6)
00_0100
>>> msb (4 :: Signed 6)
0

lsb :: BitPack a => a -> Bit Source #

Get the least significant bit.

>>> pack (-9 :: Signed 6)
11_0111
>>> lsb (-9 :: Signed 6)
1
>>> pack (-8 :: Signed 6)
11_1000
>>> lsb (-8 :: Signed 6)
0