clash-prelude-1.1.0: 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 HaskellSafe
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • BangPatterns
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • MagicHash
  • KindSignatures
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Class.Resize

Description

 
Synopsis

Documentation

class Resize (f :: Nat -> Type) where Source #

Coerce a value to be represented by a different number of bits

Minimal complete definition

resize, zeroExtend, truncateB

Methods

resize :: (KnownNat a, KnownNat b) => f a -> f b Source #

A sign-preserving resize operation

  • For signed datatypes: Increasing the size of the number replicates the sign bit to the left. Truncating a number to length L keeps the sign bit and the rightmost L-1 bits.
  • For unsigned datatypes: Increasing the size of the number extends with zeros to the left. Truncating a number of length N to a length L just removes the left (most significant) N-L bits.

extend :: (KnownNat a, KnownNat b) => f a -> f (b + a) Source #

Perform a zeroExtend for unsigned datatypes, and signExtend for a signed datatypes

zeroExtend :: (KnownNat a, KnownNat b) => f a -> f (b + a) Source #

Add extra zero bits in front of the MSB

signExtend :: (KnownNat a, KnownNat b) => f a -> f (b + a) Source #

Add extra sign bits in front of the MSB

truncateB :: KnownNat a => f (a + b) -> f a Source #

Remove bits from the MSB

Instances

Instances details
Resize BitVector Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

resize :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => BitVector a -> BitVector b Source #

extend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => BitVector a -> BitVector (b + a) Source #

zeroExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => BitVector a -> BitVector (b + a) Source #

signExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => BitVector a -> BitVector (b + a) Source #

truncateB :: forall (a :: Nat) (b :: Nat). KnownNat a => BitVector (a + b) -> BitVector a Source #

Resize Index Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

resize :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index b Source #

extend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

zeroExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

signExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

truncateB :: forall (a :: Nat) (b :: Nat). KnownNat a => Index (a + b) -> Index a Source #

Resize Unsigned Source # 
Instance details

Defined in Clash.Sized.Internal.Unsigned

Methods

resize :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Unsigned a -> Unsigned b Source #

extend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Unsigned a -> Unsigned (b + a) Source #

zeroExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Unsigned a -> Unsigned (b + a) Source #

signExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Unsigned a -> Unsigned (b + a) Source #

truncateB :: forall (a :: Nat) (b :: Nat). KnownNat a => Unsigned (a + b) -> Unsigned a Source #

Resize Signed Source # 
Instance details

Defined in Clash.Sized.Internal.Signed

Methods

resize :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Signed a -> Signed b Source #

extend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Signed a -> Signed (b + a) Source #

zeroExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Signed a -> Signed (b + a) Source #

signExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Signed a -> Signed (b + a) Source #

truncateB :: forall (a :: Nat) (b :: Nat). KnownNat a => Signed (a + b) -> Signed a Source #