clash-prelude-1.9.0: Clash: a functional hardware description language - Prelude library
Copyright(C) 2025 Martijn Bastiaan
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Class.NumConvert

Description

Utilities for converting between Clash number types in a non-erroring way. Its existence is motivated by the observation that Clash users often need to convert between different number types (e.g., Unsigned to Signed) and that it is not always clear how to do so properly. Two classes are exported:

  • NumConvert: for conversions that, based on types, are guaranteed to succeed.
  • MaybeNumConvert: for conversions that may fail for some values.

As opposed to fromIntegral, all conversions are translatable to synthesizable HDL.

Relation to convertible

Expand

Type classes exported here are similar to the convertible package in that it aims to facilitate conversions between different types. It is different in three ways:

  1. It offers no partial functions
  2. All its conversions are translatable to synthesizable HDL
  3. It is focused on (Clash's) number types
Synopsis

Documentation

class NumConvert a b where Source #

Conversions that are, based on their types, guaranteed to succeed. A successful conversion retains the numerical value interpretation of the source type in the target type and does not produce errors.

Laws

Expand

A conversion is successful if a round trip conversion is lossless. I.e.,

Just x == maybeNumConvert (numConvert @a @b x)

for all values x of type a. It should also preserve the numerical value interpretation of the bits. For types that have an Integral instance, this intuition is captured by:

toInteger x == toInteger (numConvert @a @b x)

Instances should make sure their constraints are as "tight" as possible. I.e., if an instance's constraints cannot be satisfied, then for the same types maybeNumConvert should return Nothing for one or more values in the domain of the source type a:

L.any isNothing (L.map (maybeNumConvert @a @b) [minBound ..])

All implementations should be total, i.e., they should not produce "bottoms".

Additionally, any implementation should be translatable to synthesizable HDL.

Methods

numConvert :: a -> b Source #

Convert a supplied value of type a to a value of type b. The conversion is guaranteed to succeed.

>>> numConvert (3 :: Index 8) :: Unsigned 8
3

The following will fail with a type error, as we cannot prove that all values of Index 8 can be represented by an Unsigned 2:

>>> numConvert (3 :: Index 8) :: Unsigned 2
...

For the time being, if the input is an XException, then the output is too. This property might be relaxed in the future.

Instances

Instances details
NumConvert (Signed 64) a => NumConvert Int a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Int -> a Source #

NumConvert (Signed 8) a => NumConvert Int8 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Int8 -> a Source #

NumConvert (Signed 16) a => NumConvert Int16 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Int16 -> a Source #

NumConvert (Signed 32) a => NumConvert Int32 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Int32 -> a Source #

NumConvert (Signed 64) a => NumConvert Int64 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Int64 -> a Source #

NumConvert (Unsigned 64) a => NumConvert Word a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Word -> a Source #

NumConvert (Unsigned 8) a => NumConvert Word8 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Word8 -> a Source #

NumConvert (Unsigned 16) a => NumConvert Word16 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Word16 -> a Source #

NumConvert (Unsigned 32) a => NumConvert Word32 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Word32 -> a Source #

NumConvert (Unsigned 64) a => NumConvert Word64 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Word64 -> a Source #

NumConvert a (BitVector 1) => NumConvert a Bit Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Bit Source #

NumConvert a (Signed 8) => NumConvert a Int8 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Int8 Source #

NumConvert a (Signed 16) => NumConvert a Int16 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Int16 Source #

NumConvert a (Signed 32) => NumConvert a Int32 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Int32 Source #

NumConvert a (Signed 64) => NumConvert a Int64 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Int64 Source #

NumConvert a (Signed 64) => NumConvert a Int Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Int Source #

NumConvert a (Unsigned 8) => NumConvert a Word8 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Word8 Source #

NumConvert a (Unsigned 16) => NumConvert a Word16 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Word16 Source #

NumConvert a (Unsigned 32) => NumConvert a Word32 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Word32 Source #

NumConvert a (Unsigned 64) => NumConvert a Word64 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Word64 Source #

NumConvert a (Unsigned 64) => NumConvert a Word Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: a -> Word Source #

NumConvert (BitVector 1) a => NumConvert Bit a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Bit -> a Source #

(KnownNat n, KnownNat m, n <= m) => NumConvert (BitVector n) (BitVector m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

(KnownNat n, KnownNat m, (n + 1) <= m) => NumConvert (BitVector n) (Signed m) Source #

Note: Conversion from BitVector 0 to Signed 0 is lossless, but not within the constraints of the instance.

Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

(KnownNat n, KnownNat m, n <= m) => NumConvert (BitVector n) (Unsigned m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

(KnownNat n, KnownNat m, 1 <= m, (2 ^ n) <= m) => NumConvert (BitVector n) (Index m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: BitVector n -> Index m Source #

(KnownNat n, KnownNat m, 1 <= n, n <= (2 ^ m)) => NumConvert (Index n) (BitVector m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Index n -> BitVector m Source #

(KnownNat n, KnownNat m, 1 <= n, (CLog 2 n + 1) <= m) => NumConvert (Index n) (Signed m) Source #

Note: Conversion from Index 1 to Signed 0 is lossless, but not within the constraints of the instance.

Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Index n -> Signed m Source #

(KnownNat n, KnownNat m, 1 <= n, n <= (2 ^ m)) => NumConvert (Index n) (Unsigned m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Index n -> Unsigned m Source #

(KnownNat n, KnownNat m, n <= m) => NumConvert (Index n) (Index m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Index n -> Index m Source #

(KnownNat n, KnownNat m, n <= m) => NumConvert (Unsigned n) (BitVector m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

(KnownNat n, KnownNat m, (n + 1) <= m) => NumConvert (Unsigned n) (Signed m) Source #

Note: Conversion from Unsigned 0 to Signed 0 is lossless, but not within the constraints of the instance.

Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Unsigned n -> Signed m Source #

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

Defined in Clash.Class.NumConvert.Internal.NumConvert

(KnownNat n, KnownNat m, 1 <= m, (2 ^ n) <= m) => NumConvert (Unsigned n) (Index m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Unsigned n -> Index m Source #

(KnownNat n, KnownNat m, n <= m) => NumConvert (Signed n) (Signed m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.NumConvert

Methods

numConvert :: Signed n -> Signed m Source #

class MaybeNumConvert a b where Source #

Conversions that may fail for some values. A successful conversion retains the numerical value interpretation of the source type in the target type. A failure is expressed by returning Nothing, never by an XException.

Laws

Expand

A conversion is either successful or it fails gracefully. I.e., it does not produces produce errors (also see Clash.XException). I.e.,

x == fromMaybe x (maybeNumConvert @a @b x >>= maybeNumConvert @b @a)

for all values x of type a. It should also preserve the numerical value interpretation of the bits. For types that have an Integral instance, this intuition is captured by:

toInteger x == fromMaybe (toInteger x) (toInteger (numConvert @a @b x))

If a conversion succeeds one way, it should also succeed the other way. I.e.,

isJust (maybeNumConvert @a @b x) `implies` isJust (maybeNumConvert @a @b x >>= maybeNumConvert @b @a)

A conversion should succeed if and only if the value is representable in the target type. For types that have a Bounded and Integral instance, this intuition is captured by:

isJust (maybeNumConvert @a @b x) == (i x >= i (minBound @b) && i x <= i (maxBound @b))

where i = toInteger.

All implementations should be total, i.e., they should not produce "bottoms".

Additionally, any implementation should be translatable to synthesizable HDL.

Methods

maybeNumConvert :: a -> Maybe b Source #

Convert a supplied value of type a to a value of type b. If the value cannot be represented in the target type, Nothing is returned.

>>> maybeNumConvert (1 :: Index 8) :: Maybe (Unsigned 2)
Just 1
>>> maybeNumConvert (7 :: Index 8) :: Maybe (Unsigned 2)
Nothing

For the time being, if the input is an XException, then the output is too. This property might be relaxed in the future.

Instances

Instances details
MaybeNumConvert (Signed 64) a => MaybeNumConvert Int a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Signed 8) a => MaybeNumConvert Int8 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Signed 16) a => MaybeNumConvert Int16 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Signed 32) a => MaybeNumConvert Int32 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Signed 64) a => MaybeNumConvert Int64 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Unsigned 64) a => MaybeNumConvert Word a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Unsigned 8) a => MaybeNumConvert Word8 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Unsigned 16) a => MaybeNumConvert Word16 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Unsigned 32) a => MaybeNumConvert Word32 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (Unsigned 64) a => MaybeNumConvert Word64 a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (BitVector 1) => MaybeNumConvert a Bit Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Signed 8) => MaybeNumConvert a Int8 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Signed 16) => MaybeNumConvert a Int16 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Signed 32) => MaybeNumConvert a Int32 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Signed 64) => MaybeNumConvert a Int64 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Unsigned 8) => MaybeNumConvert a Word8 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Unsigned 16) => MaybeNumConvert a Word16 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Unsigned 32) => MaybeNumConvert a Word32 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Unsigned 64) => MaybeNumConvert a Word64 Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert a (Unsigned 64) => MaybeNumConvert a Word Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

MaybeNumConvert (BitVector 1) a => MaybeNumConvert Bit a Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m) => MaybeNumConvert (BitVector n) (Signed m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m) => MaybeNumConvert (BitVector n) (Index m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m, 1 <= n) => MaybeNumConvert (Index n) (BitVector m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m, 1 <= n) => MaybeNumConvert (Index n) (Signed m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m, 1 <= n) => MaybeNumConvert (Index n) (Unsigned m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m) => MaybeNumConvert (Index n) (Index m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (BitVector m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (Signed m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

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

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert

(KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (Index m) Source # 
Instance details

Defined in Clash.Class.NumConvert.Internal.MaybeNumConvert