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

Clash.Class.Num

Description

 
Synopsis

Arithmetic functions for arguments and results of different precision

class ExtendingNum a b where Source #

Adding, subtracting, and multiplying values of two different (sub-)types.

Associated Types

type AResult a b Source #

Type of the result of the addition or subtraction

type MResult a b Source #

Type of the result of the multiplication

Methods

add :: a -> b -> AResult a b Source #

Add values of different (sub-)types, return a value of a (sub-)type that is potentially different from either argument.

sub :: a -> b -> AResult a b Source #

Subtract values of different (sub-)types, return a value of a (sub-)type that is potentially different from either argument.

mul :: a -> b -> MResult a b Source #

Multiply values of different (sub-)types, return a value of a (sub-)type that is potentially different from either argument.

Instances

Instances details
(KnownNat m, KnownNat n) => ExtendingNum (BitVector m) (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Associated Types

type AResult (BitVector m) (BitVector n) Source #

type MResult (BitVector m) (BitVector n) Source #

ExtendingNum (Index m) (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Associated Types

type AResult (Index m) (Index n) Source #

type MResult (Index m) (Index n) Source #

Methods

add :: Index m -> Index n -> AResult (Index m) (Index n) Source #

sub :: Index m -> Index n -> AResult (Index m) (Index n) Source #

mul :: Index m -> Index n -> MResult (Index m) (Index n) Source #

(KnownNat m, KnownNat n) => ExtendingNum (Unsigned m) (Unsigned n) Source # 
Instance details

Defined in Clash.Sized.Internal.Unsigned

Associated Types

type AResult (Unsigned m) (Unsigned n) Source #

type MResult (Unsigned m) (Unsigned n) Source #

ExtendingNum (Signed m) (Signed n) Source # 
Instance details

Defined in Clash.Sized.Internal.Signed

Associated Types

type AResult (Signed m) (Signed n) Source #

type MResult (Signed m) (Signed n) Source #

Methods

add :: Signed m -> Signed n -> AResult (Signed m) (Signed n) Source #

sub :: Signed m -> Signed n -> AResult (Signed m) (Signed n) Source #

mul :: Signed m -> Signed n -> MResult (Signed m) (Signed n) Source #

ENumFixedC rep int1 frac1 int2 frac2 => ExtendingNum (Fixed rep int1 frac1) (Fixed rep int2 frac2) Source #

When used in a polymorphic setting, use the following Constraint synonyms for less verbose type signatures:

Instance details

Defined in Clash.Sized.Fixed

Associated Types

type AResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) Source #

type MResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) Source #

Methods

add :: Fixed rep int1 frac1 -> Fixed rep int2 frac2 -> AResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) Source #

sub :: Fixed rep int1 frac1 -> Fixed rep int2 frac2 -> AResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) Source #

mul :: Fixed rep int1 frac1 -> Fixed rep int2 frac2 -> MResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) Source #

Saturating arithmetic functions

data SaturationMode Source #

Determine how overflow and underflow are handled by the functions in SaturatingNum

Constructors

SatWrap

Wrap around on overflow and underflow

SatBound

Become maxBound on overflow, and minBound on underflow

SatZero

Become 0 on overflow and underflow

SatSymmetric

Become maxBound on overflow, and (minBound + 1) on underflow for signed numbers, and minBound for unsigned numbers.

class (Bounded a, Num a) => SaturatingNum a where Source #

Num operators in which overflow and underflow behavior can be specified using SaturationMode.

Minimal complete definition

satAdd, satSub, satMul

Methods

satAdd :: SaturationMode -> a -> a -> a Source #

Addition with parameterizable over- and underflow behavior

satSub :: SaturationMode -> a -> a -> a Source #

Subtraction with parameterizable over- and underflow behavior

satMul :: SaturationMode -> a -> a -> a Source #

Multiplication with parameterizable over- and underflow behavior

satSucc :: SaturationMode -> a -> a Source #

Get successor of (or in other words, add 1 to) given number

satPred :: SaturationMode -> a -> a Source #

Get predecessor of (or in other words, subtract 1 from) given number

Instances

Instances details
KnownNat n => SaturatingNum (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

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

Defined in Clash.Sized.Internal.Index

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

Defined in Clash.Sized.Internal.Unsigned

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

Defined in Clash.Sized.Internal.Signed

NumFixedC rep int frac => SaturatingNum (Fixed rep int frac) Source # 
Instance details

Defined in Clash.Sized.Fixed

Methods

satAdd :: SaturationMode -> Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac Source #

satSub :: SaturationMode -> Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac Source #

satMul :: SaturationMode -> Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac Source #

satSucc :: SaturationMode -> Fixed rep int frac -> Fixed rep int frac Source #

satPred :: SaturationMode -> Fixed rep int frac -> Fixed rep int frac Source #

boundedAdd :: SaturatingNum a => a -> a -> a Source #

Addition that clips to maxBound on overflow, and minBound on underflow

boundedSub :: SaturatingNum a => a -> a -> a Source #

Subtraction that clips to maxBound on overflow, and minBound on underflow

boundedMul :: SaturatingNum a => a -> a -> a Source #

Multiplication that clips to maxBound on overflow, and minBound on underflow