clash-prelude-0.99.1: 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
  • MonoLocalBinds
  • TypeFamilies
  • DataKinds
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • KindSignatures
  • ExplicitNamespaces

Clash.Class.Num

Contents

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.

Minimal complete definition

plus, minus, times

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

plus :: 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.

minus :: 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.

times :: 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
(KnownNat m, KnownNat n) => ExtendingNum (BitVector m) (BitVector n) Source # 
Instance details

Associated Types

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

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

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

Associated Types

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

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

Methods

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

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

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

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

Associated Types

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

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

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

Associated Types

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

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

Methods

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

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

times :: 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

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

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

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

times :: 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 behaviour can be specified using SaturationMode.

Minimal complete definition

satPlus, satMin, satMult

Methods

satPlus :: SaturationMode -> a -> a -> a Source #

Addition with parametrisable over- and underflow behaviour

satMin :: SaturationMode -> a -> a -> a Source #

Subtraction with parametrisable over- and underflow behaviour

satMult :: SaturationMode -> a -> a -> a Source #

Multiplication with parametrisable over- and underflow behaviour

Instances
KnownNat n => SaturatingNum (BitVector n) Source # 
Instance details
(KnownNat n, 1 <= n) => SaturatingNum (Index n) Source # 
Instance details
KnownNat n => SaturatingNum (Unsigned n) Source # 
Instance details
KnownNat n => SaturatingNum (Signed n) Source # 
Instance details
NumFixedC rep int frac => SaturatingNum (Fixed rep int frac) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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