Skip to content

Commit 73d2424

Browse files
Add Clash.Class.NumConvert
Utilities for safely converting between various Clash number types
1 parent 0028df1 commit 73d2424

File tree

8 files changed

+1052
-1
lines changed

8 files changed

+1052
-1
lines changed
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
ADD: `Clash.Class.Convert`: Utilities for safely converting between various Clash number types

clash-prelude/clash-prelude.cabal

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -189,6 +189,9 @@ Library
189189
Clash.Class.HasDomain.CodeGen
190190
Clash.Class.HasDomain.Common
191191
Clash.Class.Num
192+
Clash.Class.NumConvert
193+
Clash.Class.NumConvert.Internal.NumConvert
194+
Clash.Class.NumConvert.Internal.MaybeNumConvert
192195
Clash.Class.Parity
193196
Clash.Class.Resize
194197

@@ -428,10 +431,12 @@ test-suite unittests
428431
Clash.Tests.BlockRam.Blob
429432
Clash.Tests.Clocks
430433
Clash.Tests.Counter
434+
Clash.Tests.NumConvert
431435
Clash.Tests.DerivingDataRepr
432436
Clash.Tests.DerivingDataReprTypes
433437
Clash.Tests.Fixed
434438
Clash.Tests.FixedExhaustive
439+
Clash.Tests.MaybeNumConvert
435440
Clash.Tests.MaybeX
436441
Clash.Tests.NFDataX
437442
Clash.Tests.NumNewtypes
Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,37 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE MonoLocalBinds #-}
3+
{-# LANGUAGE UndecidableInstances #-}
4+
5+
{- |
6+
Copyright : (C) 2025 , Martijn Bastiaan
7+
License : BSD2 (see the file LICENSE)
8+
Maintainer : QBayLogic B.V. <[email protected]>
9+
10+
Utilities for converting between Clash number types in a non-erroring way. Its
11+
existence is motivated by the observation that Clash users often need to convert
12+
between different number types (e.g., 'Clash.Sized.Unsigned.Unsigned' to
13+
'Clash.Sized.Signed.Signed') and that it is not always clear how to do so
14+
properly. Two classes are exported:
15+
16+
* 'NumConvert': for conversions that, based on types, are guaranteed to succeed.
17+
* 'MaybeNumConvert': for conversions that may fail for some values.
18+
19+
As opposed to 'Prelude.fromIntegral', all conversions are translatable to
20+
synthesizable HDL.
21+
22+
== __Relation to @convertible@__
23+
Type classes exported here are similar to the @convertible@ package in that it
24+
aims to facilitate conversions between different types. It is different in three
25+
ways:
26+
27+
1. It offers no partial functions.
28+
2. All its conversions are translatable to synthesizable HDL.
29+
3. It is focused on (Clash's) number types
30+
-}
31+
module Clash.Class.NumConvert (
32+
NumConvert (..),
33+
MaybeNumConvert (..),
34+
) where
35+
36+
import Clash.Class.NumConvert.Internal.MaybeNumConvert
37+
import Clash.Class.NumConvert.Internal.NumConvert
Lines changed: 167 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,167 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE FlexibleInstances #-}
3+
{-# LANGUAGE GADTs #-}
4+
{-# LANGUAGE MultiParamTypeClasses #-}
5+
{-# LANGUAGE UndecidableInstances #-}
6+
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.Extra.Solver #-}
7+
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.KnownNat.Solver #-}
8+
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.Normalise #-}
9+
{-# OPTIONS_HADDOCK hide #-}
10+
11+
{- |
12+
Copyright : (C) 2025 , Martijn Bastiaan
13+
License : BSD2 (see the file LICENSE)
14+
Maintainer : QBayLogic B.V. <[email protected]>
15+
-}
16+
module Clash.Class.NumConvert.Internal.MaybeNumConvert where
17+
18+
import Clash.Class.BitPack
19+
import Clash.Class.Resize
20+
import Clash.Sized.BitVector
21+
import Clash.Sized.Index
22+
import Clash.Sized.Signed
23+
import Clash.Sized.Unsigned
24+
25+
import GHC.TypeLits (KnownNat, type (+), type (<=), type (^))
26+
import GHC.TypeLits.Extra (CLog)
27+
28+
import Data.Int (Int16, Int32, Int64, Int8)
29+
import Data.Word (Word16, Word32, Word64, Word8)
30+
31+
{- $setup
32+
>>> import Clash.Prelude
33+
>>> import Clash.Class.NumConvert
34+
-}
35+
36+
{- | Conversions that may fail for some values. A successful conversion retains
37+
the numerical value interpretation of the source type in the target type. A
38+
failure is expressed by returning 'Nothing', never by an 'XException'.
39+
40+
== __Laws__
41+
A conversion is either successful or it fails gracefully. I.e., it does not
42+
produces produce errors (also see "Clash.XException"). I.e.,
43+
44+
> x == fromMaybe x (maybeNumConvert @a @b x >>= maybeNumConvert @b @a)
45+
46+
for all values @x@ of type @a@. It should also preserve the numerical value
47+
interpretation of the bits. For types that have an "Integral" instance, this
48+
intuition is captured by:
49+
50+
> toInteger x == fromMaybe (toInteger x) (toInteger (numConvert @a @b x))
51+
52+
If a conversion succeeds one way, it should also succeed the other way. I.e.,
53+
54+
> isJust (maybeNumConvert @a @b x) `implies` isJust (maybeNumConvert @a @b x >>= maybeNumConvert @b @a)
55+
56+
A conversion should succeed if and only if the value is representable in the
57+
target type. For types that have a "Bounded" and "Integral" instance, this
58+
intuition is captured by:
59+
60+
> isJust (maybeNumConvert @a @b x) == (i x >= i (minBound @b) && i x <= i (maxBound @b))
61+
62+
where @i = toInteger@.
63+
64+
All implementations should be total, i.e., they should not produce \"bottoms\".
65+
66+
Additionally, any implementation should be translatable to synthesizable HDL.
67+
-}
68+
class MaybeNumConvert a b where
69+
{- | NumConvert a supplied value of type @a@ to a value of type @b@. If the value
70+
cannot be represented in the target type, 'Nothing' is returned.
71+
72+
>>> maybeNumConvert (1 :: Index 8) :: Maybe (Unsigned 2)
73+
Just 1
74+
>>> maybeNumConvert (7 :: Index 8) :: Maybe (Unsigned 2)
75+
Nothing
76+
77+
For the time being, if the input is an 'XException', then the output is too.
78+
This property might be relaxed in the future.
79+
-}
80+
maybeNumConvert :: a -> Maybe b
81+
82+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Index n) (Index m) where
83+
maybeNumConvert !a = maybeResize a
84+
85+
instance (KnownNat n, KnownNat m, 1 <= n) => MaybeNumConvert (Index n) (Unsigned m) where
86+
maybeNumConvert !a = maybeResize $ bitCoerce @_ @(Unsigned (CLog 2 n)) a
87+
88+
instance (KnownNat n, KnownNat m, 1 <= n) => MaybeNumConvert (Index n) (Signed m) where
89+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Unsigned (CLog 2 n)) a
90+
91+
instance (KnownNat n, KnownNat m, 1 <= n) => MaybeNumConvert (Index n) (BitVector m) where
92+
maybeNumConvert !a = maybeResize $ pack a
93+
94+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Unsigned n) (Index m) where
95+
maybeNumConvert !a = maybeResize $ bitCoerce @_ @(Index (2 ^ n)) a
96+
97+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Unsigned n) (Unsigned m) where
98+
maybeNumConvert !a = maybeResize a
99+
100+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Unsigned n) (Signed m) where
101+
maybeNumConvert !a = maybeResize $ bitCoerce @(Unsigned (n + 1)) $ extend a
102+
103+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Unsigned n) (BitVector m) where
104+
maybeNumConvert !a = maybeResize $ pack a
105+
106+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (Index m) where
107+
maybeNumConvert n
108+
| n < 0 = Nothing
109+
| otherwise = maybeResize (bitCoerce @_ @(Index (2 ^ n)) (resize n))
110+
111+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (Unsigned m) where
112+
maybeNumConvert n
113+
| n < 0 = Nothing
114+
| otherwise = maybeResize (bitCoerce @(Signed (n + 1)) (extend n))
115+
116+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (Signed m) where
117+
maybeNumConvert !a = maybeResize a
118+
119+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (Signed n) (BitVector m) where
120+
maybeNumConvert n
121+
| n < 0 = Nothing
122+
| otherwise = maybeResize (pack @(Signed (n + 1)) (extend n))
123+
124+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (BitVector n) (Index m) where
125+
maybeNumConvert !a = maybeResize $ unpack @(Index (2 ^ n)) a
126+
127+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (BitVector n) (Unsigned m) where
128+
maybeNumConvert !a = maybeResize $ unpack @(Unsigned n) a
129+
130+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (BitVector n) (Signed m) where
131+
maybeNumConvert !a = maybeResize $ unpack @(Signed (n + 1)) $ extend a
132+
133+
instance (KnownNat n, KnownNat m) => MaybeNumConvert (BitVector n) (BitVector m) where
134+
maybeNumConvert !a = maybeResize a
135+
136+
instance (MaybeNumConvert (Unsigned 64) a) => MaybeNumConvert Word a where
137+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Unsigned 64) a
138+
instance (MaybeNumConvert (Unsigned 64) a) => MaybeNumConvert Word64 a where
139+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Unsigned 64) a
140+
instance (MaybeNumConvert (Unsigned 32) a) => MaybeNumConvert Word32 a where
141+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Unsigned 32) a
142+
instance (MaybeNumConvert (Unsigned 16) a) => MaybeNumConvert Word16 a where
143+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Unsigned 16) a
144+
instance (MaybeNumConvert (Unsigned 8) a) => MaybeNumConvert Word8 a where
145+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Unsigned 8) a
146+
147+
instance (MaybeNumConvert (Signed 64) a) => MaybeNumConvert Int a where
148+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Signed 64) a
149+
instance (MaybeNumConvert (Signed 64) a) => MaybeNumConvert Int64 a where
150+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Signed 64) a
151+
instance (MaybeNumConvert (Signed 32) a) => MaybeNumConvert Int32 a where
152+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Signed 32) a
153+
instance (MaybeNumConvert (Signed 16) a) => MaybeNumConvert Int16 a where
154+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Signed 16) a
155+
instance (MaybeNumConvert (Signed 8) a) => MaybeNumConvert Int8 a where
156+
maybeNumConvert !a = maybeNumConvert $ bitCoerce @_ @(Signed 8) a
157+
158+
instance (MaybeNumConvert a (Unsigned 64)) => MaybeNumConvert a Word where
159+
maybeNumConvert !a = fmap (bitCoerce @(Unsigned 64)) $ maybeNumConvert a
160+
instance (MaybeNumConvert a (Unsigned 64)) => MaybeNumConvert a Word64 where
161+
maybeNumConvert !a = fmap (bitCoerce @(Unsigned 64)) $ maybeNumConvert a
162+
instance (MaybeNumConvert a (Unsigned 32)) => MaybeNumConvert a Word32 where
163+
maybeNumConvert !a = fmap (bitCoerce @(Unsigned 32)) $ maybeNumConvert a
164+
instance (MaybeNumConvert a (Unsigned 16)) => MaybeNumConvert a Word16 where
165+
maybeNumConvert !a = fmap (bitCoerce @(Unsigned 16)) $ maybeNumConvert a
166+
instance (MaybeNumConvert a (Unsigned 8)) => MaybeNumConvert a Word8 where
167+
maybeNumConvert !a = fmap (bitCoerce @(Unsigned 8)) $ maybeNumConvert a

0 commit comments

Comments
 (0)