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

Safe HaskellNone
LanguageHaskell2010

CLaSH.Sized.Fixed

Contents

Description

Fixed point numbers

  • The Num operators for the given types saturate on overflow, and use truncation as the rounding method.
  • Use $$(fLit d) to create Fixed point number literals.
  • Use Constraint synonyms when writing type signatures for polymorphic functions that use Fixed point numbers.

BEWARE: rounding by truncation introduces a sign bias!

  • Truncation for positive numbers effectively results in: round towards zero.
  • Truncation for negative numbers effectively results in: round towards -infinity.

Synopsis

SFixed: Signed Fixed point numbers

type SFixed int frac = Fixed frac Signed (int + frac) Source

Signed Fixed-point number, with int integer bits (including sign-bit) and frac fractional bits.

  • The range SFixed int frac numbers is: [-(2^(int -1)) .. 2^(int-1) - 2^-frac ]
  • The resolution of SFixed int frac numbers is: 2^frac
  • The Num operators for this type saturate on overflow, and use truncation as the rounding method.
>>> maxBound :: SFixed 3 4
3.9375
>>> minBound :: SFixed 3 4
-4.0
>>> (1 :: SFixed 3 4) + (2 :: SFixed 3 4)
3.0
>>> (2 :: SFixed 3 4) + (3 :: SFixed 3 4)
3.9375
>>> (-2 :: SFixed 3 4) + (-3 :: SFixed 3 4)
-4.0
>>> ($$(fLit 1.375) :: SFixed 3 4) * ($$(fLit -0.8125) :: SFixed 3 4)
-1.125
>>> ($$(fLit 1.375) :: SFixed 3 4) `mult` ($$(fLit -0.8125) :: SFixed 3 4) :: SFixed 6 8
-1.1171875
>>> (2 :: SFixed 3 4) `plus` (3 :: SFixed 3 4) :: SFixed 4 4
5.0
>>> (-2 :: SFixed 3 4) `plus` (-3 :: SFixed 3 4) :: SFixed 4 4
-5.0

sf Source

Arguments

:: SNat frac

Position of the virtual point

-> Signed (int + frac)

The Signed integer

-> SFixed int frac 

Treat a Signed integer as a Signed Fixed-point integer

>>> sf d4 (-22 :: Signed 7)
-1.375

unSF :: SFixed int frac -> Signed (int + frac) Source

See the underlying representation of a Signed Fixed-point integer

UFixed: Unsigned Fixed point numbers

type UFixed int frac = Fixed frac Unsigned (int + frac) Source

Unsigned Fixed-point number, with int integer bits and frac fractional bits

  • The range UFixed int frac numbers is: [0 .. 2^int - 2^-frac ]
  • The resolution of UFixed int frac numbers is: 2^frac
  • The Num operators for this type saturate on overflow, and use truncation as the rounding method.
>>> maxBound :: UFixed 3 4
7.9375
>>> minBound :: UFixed 3 4
0.0
>>> (1 :: UFixed 3 4) + (2 :: UFixed 3 4)
3.0
>>> (2 :: UFixed 3 4) + (6 :: UFixed 3 4)
7.9375
>>> (1 :: UFixed 3 4) - (3 :: UFixed 3 4)
0.0
>>> ($$(fLit 1.375) :: UFixed 3 4) * ($$(fLit 0.8125) :: UFixed 3 4)
1.0625
>>> ($$(fLit 1.375) :: UFixed 3 4) `mult` ($$(fLit 0.8125) :: UFixed 3 4) :: UFixed 6 8
1.1171875
>>> (2 :: UFixed 3 4) `plus` (6 :: UFixed 3 4) :: UFixed 4 4
8.0

However, minus does not saturate to minBound on underflow:

>>> (1 :: UFixed 3 4) `minus` (3 :: UFixed 3 4) :: UFixed 4 4
14.0

uf Source

Arguments

:: SNat frac

Position of the virtual point

-> Unsigned (int + frac)

The Unsigned integer

-> UFixed int frac 

Treat an Unsigned integer as a Unsigned Fixed-point number

>>> uf d4 (92 :: Unsigned 7)
5.75

unUF :: UFixed int frac -> Unsigned (int + frac) Source

See the underlying representation of an Unsigned Fixed-point integer

Fixed point literals

fLit :: forall frac rep size. (KnownNat frac, Num (rep size), Bounded (rep size), Integral (rep size)) => Double -> Q (TExp (Fixed frac rep size)) Source

Convert, at compile-time, a Double literal to a Fixed-point literal. The conversion saturates on overflow, and uses truncation as its rounding method.

So when you type:

n = $$(fLit 2.2867) :: SFixed 4 4

The compiler sees:

n = Fixed (fromInteger 45) :: SFixed 4 4

Upon evaluation you see that the value is rounded / truncated in accordance to the fixed point representation:

>>> n
2.8125

Fixed point wrapper

newtype Fixed frac rep size Source

Fixed-point number

Where:

  • frac denotes the position of the virtual point counting from the LSB
  • rep is the underlying representation
  • size is the number of bits used to represent the number

The Num operators for this type saturate on overflow, and use truncation as the rounding method.

Constructors

Fixed 

Fields

unFixed :: rep size
 

Instances

Bounded (rep size) => Bounded (Fixed frac rep size) 
Eq (rep size) => Eq (Fixed frac rep size) 
NumFixed frac rep size => Num (Fixed frac rep size)

The operators of this instance saturate on overflow, and use truncation as the rounding method.

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

Ord (rep size) => Ord (Fixed frac rep size) 
(Show (rep size), Bits (rep size), KnownNat frac, Integral (rep size)) => Show (Fixed frac rep size) 
Default (rep size) => Default (Fixed frac rep size) 
(Lift (rep size), KnownNat frac, KnownNat size, Typeable (Nat -> *) rep) => Lift (Fixed frac rep size) 
BitVector (rep size) => BitVector (Fixed frac rep size) 
CPack (Fixed frac rep size) 
MultFixed rep frac1 frac2 size1 size2 => Mult (Fixed frac1 rep size1) (Fixed frac2 rep size2)

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

AddFixed rep frac1 frac2 size1 size2 => Add (Fixed frac1 rep size1) (Fixed frac2 rep size2)

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

type CSignalP clk (Fixed frac rep size) = CSignal clk (Fixed frac rep size) 
type BitSize (Fixed frac rep size) = BitSize (rep size) 
type MResult (Fixed frac1 rep size1) (Fixed frac2 rep size2) = Fixed ((+) frac1 frac2) rep ((+) size1 size2) 
type AResult (Fixed frac1 rep size1) (Fixed frac2 rep size2) = Fixed (Max frac1 frac2) rep ((+) (Max size1 size2) 1) 

resizeF :: forall frac1 frac2 rep size1 size2. ResizeFC rep frac1 frac2 size1 size2 => Fixed frac1 rep size1 -> Fixed frac2 rep size2 Source

Saturating resize operation, truncates for rounding

>>> $$(fLit 0.8125) :: SFixed 3 4
0.8125
>>> resizeF ($$(fLit 0.8125) :: SFixed 3 4) :: SFixed 2 3
0.75
>>> $$(fLit 3.4) :: SFixed 3 4
3.375
>>> resizeF ($$(fLit 3.4) :: SFixed 3 4) :: SFixed 2 3
1.875
>>> maxBound :: SFixed 2 3
1.875

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

fracShift :: KnownNat frac => Fixed frac rep size -> Int Source

Get the position of the virtual point of a Fixed-point number

satN2 :: SatN2C rep n => rep (n + 2) -> rep n Source

Resize an (N+2)-bits number to an N-bits number, saturates to minBound or maxBound when the argument does not fit within the representations bounds of the result.

Uses cheaper saturation than resizeF, which is made possible by knowing that we only reduce the size by 2 bits.

>>> (2 :: Unsigned 2) + (3 :: Unsigned 2)
1
>>> satN2 (resize (2 :: Unsigned 2) + resize (3 :: Unsigned 2)) :: Unsigned 2
3
>>> satN2 (resize (1 :: Unsigned 2) + resize (1 :: Unsigned 2)) :: Unsigned 2
2
>>> (2 :: Unsigned 2) - (3 :: Unsigned 2)
3
>>> satN2 (resize (2 :: Unsigned 2) - resize (3 :: Unsigned 2)) :: Unsigned 2
0
>>> (2 :: Signed 3) + (3 :: Signed 3)
-3
>>> satN2 (resize (2 :: Signed 3) + resize (3 :: Signed 3)) :: Signed 3
3

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

Constraint synonyms

Writing polymorphic functions over fixed point numbers can be a potentially verbose due to the many class constraints induced by the functions and operators of this module.

Writing a simple multiply-and-accumulate function can already give rise to many lines of constraints:

mac :: ( 1 <= (int + frac), (((int + frac) + 1) + 1) ~ ((int + frac) + 2)
       , KnownNat (frac + frac), KnownNat ((int + frac) + (int + frac))
       , KnownNat ((int + frac) + 2), KnownNat (int + frac), KnownNat frac
       )
    => SFixed int frac
    -> SFixed int frac
    -> SFixed int frac
    -> SFixed int frac
mac s x y = s + (x * y)

But with constraint synonyms, you can write the type signature like this:

mac :: NumSFixed int frac
    => SFixed int frac
    -> SFixed int frac
    -> SFixed int frac
    -> SFixed int frac
mac s x y = s + (x * y)

Where NumSFixed refers to the Constraints needed by the operators of the Num class for the SFixed datatype.

Constraint synonyms for SFixed

type NumSFixed int frac = (1 <= (int + frac), (((int + frac) + 1) + 1) ~ ((int + frac) + 2), KnownNat (frac + frac), KnownNat ((int + frac) + (int + frac)), KnownNat ((int + frac) + 2), KnownNat (int + frac), KnownNat frac) Source

Constraint for the Num instance of SFixed

type AddSFixed int1 frac1 int2 frac2 = AddFixed Signed frac1 frac2 (int1 + frac1) (int2 + frac2) Source

Constraint for the Add instance of SFixed

type MultSFixed int1 frac1 int2 frac2 = MultFixed Signed frac1 frac2 (int1 + frac1) (int2 + frac2) Source

Constraint for the Mult instance of SFixed

type ResizeSFC int1 frac1 int2 frac2 = (KnownNat (int2 + frac2), KnownNat (int1 + frac1), KnownNat frac1, KnownNat frac2) Source

Constraint for the resizeF function, specialized for SFixed

Constraint synonyms for UFixed

type NumUFixed int frac = (1 <= (int + frac), (((int + frac) + 1) + 1) ~ ((int + frac) + 2), KnownNat (frac + frac), KnownNat ((int + frac) + (int + frac)), KnownNat ((int + frac) + 2), KnownNat (int + frac), KnownNat frac) Source

Constraint for the Num instance of UFixed

type AddUFixed int1 frac1 int2 frac2 = AddFixed Unsigned frac1 frac2 (int1 + frac1) (int2 + frac2) Source

Constraint for the Add instance of UFixed

type MultUFixed int1 frac1 int2 frac2 = MultFixed Unsigned frac1 frac2 (int1 + frac1) (int2 + frac2) Source

Constraint for the Mult instance of UFixed

type ResizeUFC int1 frac1 int2 frac2 = (KnownNat (int2 + frac2), KnownNat (int1 + frac1), KnownNat frac1, KnownNat frac2) Source

Constraint for the resizeF function, specialized for UFixed

Constraint synonyms for Fixed wrapper

type NumFixed frac rep size = (SatN2C rep size, ResizeFC rep (frac + frac) frac (size + size) size, Num (rep size), Num (rep (size + 2)), Mult (rep size) (rep size), MResult (rep size) (rep size) ~ rep (size + size)) Source

Constraint for the Num instance of Fixed

type AddFixed rep frac1 frac2 size1 size2 = (ResizeFC rep frac1 (Max frac1 frac2) size1 (Max size1 size2 + 1), ResizeFC rep frac2 (Max frac1 frac2) size2 (Max size1 size2 + 1), Num (rep (Max size1 size2 + 1))) Source

Constraint for the Add instance of Fixed

type MultFixed rep frac1 frac2 size1 size2 = (Mult (rep size1) (rep size2), MResult (rep size1) (rep size2) ~ rep (size1 + size2)) Source

Constraint for the Mult instance of Fixed

type ResizeFC rep frac1 frac2 size1 size2 = (Bounded (rep size2), Eq (rep size1), Ord (rep size1), Num (rep size1), Bits (rep size1), Resize rep, KnownNat size2, KnownNat size1, Bits (rep size2), KnownNat frac2, KnownNat frac1, Bounded (rep size1)) Source

Constraint for the resizeF function

type SatN2C rep n = (1 <= n, ((n + 1) + 1) ~ (n + 2), BitVector (rep n), BitVector (rep (n + 2)), BitSize (rep n) ~ n, BitSize (rep (n + 2)) ~ (n + 2), KnownNat n, KnownNat (n + 2), Bounded (rep n), Bits (rep (n + 2))) Source

Constraint for the satN2 function

Constraint synonyms for Signed and Unsigned

type SatN2SC n = (1 <= n, ((n + 1) + 1) ~ (n + 2), KnownNat n, KnownNat (n + 2)) Source

Constraint for the satN2 function, specialized for Signed

type SatN2UC n = (1 <= n, ((n + 1) + 1) ~ (n + 2), KnownNat n, KnownNat (n + 2)) Source

Constraint for the satN2 function, specialized for Unsigned

Proxy

asFracProxy :: Fixed frac rep size -> Proxy frac Source

asRepProxy :: Fixed frac rep size -> Proxy rep Source