Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
CHANGED/FIXED: `negate` for `Num Bit` is now defined as the additive inverse, i.e., `negate = id`.
1 change: 1 addition & 0 deletions clash-prelude/clash-prelude.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -452,6 +452,7 @@ test-suite unittests
Clash.Tests.XException

Clash.Tests.Laws.Enum
Clash.Tests.Laws.Num
Clash.Tests.Laws.SaturatingNum

Hedgehog.Extra
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/src/Clash/Sized/Internal/BitVector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -369,7 +369,7 @@ instance Num Bit where
(+) = xor##
(-) = xor##
(*) = and##
negate = complement##
negate = id
abs = id
signum b = b
fromInteger = fromInteger## 0##
Expand Down
51 changes: 51 additions & 0 deletions clash-prelude/tests/Clash/Tests/Laws/Num.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,51 @@
module Clash.Tests.Laws.Num (tests) where

import Clash.Tests.Laws.SaturatingNum
( genBoundedIntegral
, genUnsigned
)

import Test.Tasty
import Test.Tasty.Hedgehog.Extra

import Clash.Sized.BitVector (Bit, BitVector)

import Control.DeepSeq (NFData)
import GHC.TypeLits (KnownNat)

import Hedgehog

genBit :: Gen Bit
genBit = genBoundedIntegral

genBitVector :: forall n. KnownNat n => Gen (BitVector n)
genBitVector = genBoundedIntegral

additiveInverse :: (Num a, Show a, Eq a) => Gen a -> TestTree
additiveInverse genA = testPropertyXXX "x + negate x == 0" $ property $ do
a <- forAll genA
a + negate a === 0

testAdditiveInverse :: (NFData a, Ord a, Show a, Eq a, Num a) => String -> Gen a -> TestTree
testAdditiveInverse typeName genA =
testGroup typeName [testGroup "additiveInverse" [additiveInverse genA]]

tests :: TestTree
tests = testGroup "Num"
[ testAdditiveInverse "Bit" genBit

, testAdditiveInverse "Unsigned 0" (genUnsigned @0)
, testAdditiveInverse "Unsigned 1" (genUnsigned @1)
, testAdditiveInverse "Unsigned 32" (genUnsigned @32)
, testAdditiveInverse "Unsigned 127" (genUnsigned @127)
, testAdditiveInverse "Unsigned 128" (genUnsigned @128)

, testAdditiveInverse "BitVector 0" (genBitVector @0)
, testAdditiveInverse "BitVector 1" (genBitVector @1)
, testAdditiveInverse "BitVector 32" (genBitVector @32)
, testAdditiveInverse "BitVector 127" (genBitVector @127)
, testAdditiveInverse "BitVector 128" (genBitVector @128)

-- TODO: Index, Signed, UFixed, SFixed. See discussion in
-- https://github.com/clash-lang/clash-compiler/issues/3015
]
11 changes: 10 additions & 1 deletion clash-prelude/tests/Clash/Tests/Laws/SaturatingNum.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,16 @@
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.Normalise #-}
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.KnownNat.Solver #-}

module Clash.Tests.Laws.SaturatingNum (tests) where
module Clash.Tests.Laws.SaturatingNum
( tests

, genBoundedIntegral
, genIndex
, genSFixed
, genSigned
, genUFixed
, genUnsigned
) where

import Test.Tasty
import Test.Tasty.Hedgehog.Extra
Expand Down
2 changes: 2 additions & 0 deletions clash-prelude/tests/unittests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ import qualified Clash.Tests.Vector
import qualified Clash.Tests.XException

import qualified Clash.Tests.Laws.Enum
import qualified Clash.Tests.Laws.Num
import qualified Clash.Tests.Laws.SaturatingNum

tests :: TestTree
Expand Down Expand Up @@ -60,6 +61,7 @@ tests = testGroup "Unittests"
, Clash.Tests.XException.tests
, testGroup "Laws"
[ Clash.Tests.Laws.Enum.tests
, Clash.Tests.Laws.Num.tests
, Clash.Tests.Laws.SaturatingNum.tests
]
]
Expand Down
Loading