... |
... |
@@ -13,6 +13,7 @@ |
13
|
13
|
{-# LANGUAGE FlexibleContexts #-}
|
14
|
14
|
{-# LANGUAGE OverloadedStrings #-}
|
15
|
15
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
16
|
+{-# LANGUAGE TypeAbstractions #-}
|
16
|
17
|
{-# LANGUAGE TypeFamilies #-}
|
17
|
18
|
{-# LANGUAGE DerivingStrategies #-}
|
18
|
19
|
{-# LANGUAGE MagicHash #-}
|
... |
... |
@@ -24,7 +25,7 @@ module Main |
24
|
25
|
( main
|
25
|
26
|
) where
|
26
|
27
|
|
27
|
|
-import Data.Bits (Bits((.&.), bit))
|
|
28
|
+import Data.Bits (Bits((.&.), bit), FiniteBits, finiteBitSize)
|
28
|
29
|
import Data.Word
|
29
|
30
|
import Data.Int
|
30
|
31
|
import GHC.Natural
|
... |
... |
@@ -133,6 +134,16 @@ newtype NonZero a = NonZero { getNonZero :: a } |
133
|
134
|
instance (Arbitrary a, Num a, Eq a) => Arbitrary (NonZero a) where
|
134
|
135
|
arbitrary = nonZero
|
135
|
136
|
|
|
137
|
+-- | A newtype for shift amounts that are bounded by @wordSize - 1@
|
|
138
|
+newtype BoundedShiftAmount a = BoundedShiftAmount {getBoundedShiftAmount :: Int}
|
|
139
|
+ deriving (Eq, Ord, Show)
|
|
140
|
+
|
|
141
|
+instance (FiniteBits a) => Arbitrary (BoundedShiftAmount a) where
|
|
142
|
+ arbitrary = do
|
|
143
|
+ x <- arbitrary
|
|
144
|
+ let widthBits = finiteBitSize (undefined :: a)
|
|
145
|
+ pure $ BoundedShiftAmount (abs x `mod` widthBits)
|
|
146
|
+
|
136
|
147
|
instance Arbitrary Natural where
|
137
|
148
|
arbitrary = integralDownsize . (`mod` 10000) . abs <$> arbitraryInt64
|
138
|
149
|
|
... |
... |
@@ -395,6 +406,10 @@ class TestPrimop f where |
395
|
406
|
testPrimopDivLike :: String -> f -> f -> Test
|
396
|
407
|
testPrimopDivLike _ _ _ = error "Div testing not supported for this type."
|
397
|
408
|
|
|
409
|
+ -- | Special test method for shift operations that bounds the shift amount
|
|
410
|
+ testPrimopShift :: String -> f -> f -> Test
|
|
411
|
+ testPrimopShift _ _ _ = error "Shift testing not supported for this type."
|
|
412
|
+
|
398
|
413
|
{-
|
399
|
414
|
instance TestPrimop (Int# -> Int# -> Int#) where
|
400
|
415
|
testPrimop s l r = Property s $ \(uInt -> a1) (uInt -> a2) -> (wInt (l a1 a2)) === wInt (r a1 a2)
|
... |
... |
@@ -460,9 +475,9 @@ testPrimops = Group "primop" |
460
|
475
|
, testPrimopDivLike "quotInt8#" Primop.quotInt8# Wrapper.quotInt8#
|
461
|
476
|
, testPrimopDivLike "remInt8#" Primop.remInt8# Wrapper.remInt8#
|
462
|
477
|
, testPrimopDivLike "quotRemInt8#" Primop.quotRemInt8# Wrapper.quotRemInt8#
|
463
|
|
- , testPrimop "uncheckedShiftLInt8#" Primop.uncheckedShiftLInt8# Wrapper.uncheckedShiftLInt8#
|
464
|
|
- , testPrimop "uncheckedShiftRAInt8#" Primop.uncheckedShiftRAInt8# Wrapper.uncheckedShiftRAInt8#
|
465
|
|
- , testPrimop "uncheckedShiftRLInt8#" Primop.uncheckedShiftRLInt8# Wrapper.uncheckedShiftRLInt8#
|
|
478
|
+ , testPrimopShift "uncheckedShiftLInt8#" Primop.uncheckedShiftLInt8# Wrapper.uncheckedShiftLInt8#
|
|
479
|
+ , testPrimopShift "uncheckedShiftRAInt8#" Primop.uncheckedShiftRAInt8# Wrapper.uncheckedShiftRAInt8#
|
|
480
|
+ , testPrimopShift "uncheckedShiftRLInt8#" Primop.uncheckedShiftRLInt8# Wrapper.uncheckedShiftRLInt8#
|
466
|
481
|
, testPrimop "int8ToWord8#" Primop.int8ToWord8# Wrapper.int8ToWord8#
|
467
|
482
|
, testPrimop "eqInt8#" Primop.eqInt8# Wrapper.eqInt8#
|
468
|
483
|
, testPrimop "geInt8#" Primop.geInt8# Wrapper.geInt8#
|
... |
... |
@@ -482,8 +497,8 @@ testPrimops = Group "primop" |
482
|
497
|
, testPrimop "orWord8#" Primop.orWord8# Wrapper.orWord8#
|
483
|
498
|
, testPrimop "xorWord8#" Primop.xorWord8# Wrapper.xorWord8#
|
484
|
499
|
, testPrimop "notWord8#" Primop.notWord8# Wrapper.notWord8#
|
485
|
|
- , testPrimop "uncheckedShiftLWord8#" Primop.uncheckedShiftLWord8# Wrapper.uncheckedShiftLWord8#
|
486
|
|
- , testPrimop "uncheckedShiftRLWord8#" Primop.uncheckedShiftRLWord8# Wrapper.uncheckedShiftRLWord8#
|
|
500
|
+ , testPrimopShift "uncheckedShiftLWord8#" Primop.uncheckedShiftLWord8# Wrapper.uncheckedShiftLWord8#
|
|
501
|
+ , testPrimopShift "uncheckedShiftRLWord8#" Primop.uncheckedShiftRLWord8# Wrapper.uncheckedShiftRLWord8#
|
487
|
502
|
, testPrimop "word8ToInt8#" Primop.word8ToInt8# Wrapper.word8ToInt8#
|
488
|
503
|
, testPrimop "eqWord8#" Primop.eqWord8# Wrapper.eqWord8#
|
489
|
504
|
, testPrimop "geWord8#" Primop.geWord8# Wrapper.geWord8#
|
... |
... |
@@ -500,9 +515,9 @@ testPrimops = Group "primop" |
500
|
515
|
, testPrimopDivLike "quotInt16#" Primop.quotInt16# Wrapper.quotInt16#
|
501
|
516
|
, testPrimopDivLike "remInt16#" Primop.remInt16# Wrapper.remInt16#
|
502
|
517
|
, testPrimopDivLike "quotRemInt16#" Primop.quotRemInt16# Wrapper.quotRemInt16#
|
503
|
|
- , testPrimop "uncheckedShiftLInt16#" Primop.uncheckedShiftLInt16# Wrapper.uncheckedShiftLInt16#
|
504
|
|
- , testPrimop "uncheckedShiftRAInt16#" Primop.uncheckedShiftRAInt16# Wrapper.uncheckedShiftRAInt16#
|
505
|
|
- , testPrimop "uncheckedShiftRLInt16#" Primop.uncheckedShiftRLInt16# Wrapper.uncheckedShiftRLInt16#
|
|
518
|
+ , testPrimopShift "uncheckedShiftLInt16#" Primop.uncheckedShiftLInt16# Wrapper.uncheckedShiftLInt16#
|
|
519
|
+ , testPrimopShift "uncheckedShiftRAInt16#" Primop.uncheckedShiftRAInt16# Wrapper.uncheckedShiftRAInt16#
|
|
520
|
+ , testPrimopShift "uncheckedShiftRLInt16#" Primop.uncheckedShiftRLInt16# Wrapper.uncheckedShiftRLInt16#
|
506
|
521
|
, testPrimop "int16ToWord16#" Primop.int16ToWord16# Wrapper.int16ToWord16#
|
507
|
522
|
, testPrimop "eqInt16#" Primop.eqInt16# Wrapper.eqInt16#
|
508
|
523
|
, testPrimop "geInt16#" Primop.geInt16# Wrapper.geInt16#
|
... |
... |
@@ -522,8 +537,8 @@ testPrimops = Group "primop" |
522
|
537
|
, testPrimop "orWord16#" Primop.orWord16# Wrapper.orWord16#
|
523
|
538
|
, testPrimop "xorWord16#" Primop.xorWord16# Wrapper.xorWord16#
|
524
|
539
|
, testPrimop "notWord16#" Primop.notWord16# Wrapper.notWord16#
|
525
|
|
- , testPrimop "uncheckedShiftLWord16#" Primop.uncheckedShiftLWord16# Wrapper.uncheckedShiftLWord16#
|
526
|
|
- , testPrimop "uncheckedShiftRLWord16#" Primop.uncheckedShiftRLWord16# Wrapper.uncheckedShiftRLWord16#
|
|
540
|
+ , testPrimopShift "uncheckedShiftLWord16#" Primop.uncheckedShiftLWord16# Wrapper.uncheckedShiftLWord16#
|
|
541
|
+ , testPrimopShift "uncheckedShiftRLWord16#" Primop.uncheckedShiftRLWord16# Wrapper.uncheckedShiftRLWord16#
|
527
|
542
|
, testPrimop "word16ToInt16#" Primop.word16ToInt16# Wrapper.word16ToInt16#
|
528
|
543
|
, testPrimop "eqWord16#" Primop.eqWord16# Wrapper.eqWord16#
|
529
|
544
|
, testPrimop "geWord16#" Primop.geWord16# Wrapper.geWord16#
|
... |
... |
@@ -540,9 +555,9 @@ testPrimops = Group "primop" |
540
|
555
|
, testPrimopDivLike "quotInt32#" Primop.quotInt32# Wrapper.quotInt32#
|
541
|
556
|
, testPrimopDivLike "remInt32#" Primop.remInt32# Wrapper.remInt32#
|
542
|
557
|
, testPrimopDivLike "quotRemInt32#" Primop.quotRemInt32# Wrapper.quotRemInt32#
|
543
|
|
- , testPrimop "uncheckedShiftLInt32#" Primop.uncheckedShiftLInt32# Wrapper.uncheckedShiftLInt32#
|
544
|
|
- , testPrimop "uncheckedShiftRAInt32#" Primop.uncheckedShiftRAInt32# Wrapper.uncheckedShiftRAInt32#
|
545
|
|
- , testPrimop "uncheckedShiftRLInt32#" Primop.uncheckedShiftRLInt32# Wrapper.uncheckedShiftRLInt32#
|
|
558
|
+ , testPrimopShift "uncheckedShiftLInt32#" Primop.uncheckedShiftLInt32# Wrapper.uncheckedShiftLInt32#
|
|
559
|
+ , testPrimopShift "uncheckedShiftRAInt32#" Primop.uncheckedShiftRAInt32# Wrapper.uncheckedShiftRAInt32#
|
|
560
|
+ , testPrimopShift "uncheckedShiftRLInt32#" Primop.uncheckedShiftRLInt32# Wrapper.uncheckedShiftRLInt32#
|
546
|
561
|
, testPrimop "int32ToWord32#" Primop.int32ToWord32# Wrapper.int32ToWord32#
|
547
|
562
|
, testPrimop "eqInt32#" Primop.eqInt32# Wrapper.eqInt32#
|
548
|
563
|
, testPrimop "geInt32#" Primop.geInt32# Wrapper.geInt32#
|
... |
... |
@@ -562,8 +577,8 @@ testPrimops = Group "primop" |
562
|
577
|
, testPrimop "orWord32#" Primop.orWord32# Wrapper.orWord32#
|
563
|
578
|
, testPrimop "xorWord32#" Primop.xorWord32# Wrapper.xorWord32#
|
564
|
579
|
, testPrimop "notWord32#" Primop.notWord32# Wrapper.notWord32#
|
565
|
|
- , testPrimop "uncheckedShiftLWord32#" Primop.uncheckedShiftLWord32# Wrapper.uncheckedShiftLWord32#
|
566
|
|
- , testPrimop "uncheckedShiftRLWord32#" Primop.uncheckedShiftRLWord32# Wrapper.uncheckedShiftRLWord32#
|
|
580
|
+ , testPrimopShift "uncheckedShiftLWord32#" Primop.uncheckedShiftLWord32# Wrapper.uncheckedShiftLWord32#
|
|
581
|
+ , testPrimopShift "uncheckedShiftRLWord32#" Primop.uncheckedShiftRLWord32# Wrapper.uncheckedShiftRLWord32#
|
567
|
582
|
, testPrimop "word32ToInt32#" Primop.word32ToInt32# Wrapper.word32ToInt32#
|
568
|
583
|
, testPrimop "eqWord32#" Primop.eqWord32# Wrapper.eqWord32#
|
569
|
584
|
, testPrimop "geWord32#" Primop.geWord32# Wrapper.geWord32#
|
... |
... |
@@ -579,9 +594,9 @@ testPrimops = Group "primop" |
579
|
594
|
, testPrimop "timesInt64#" Primop.timesInt64# Wrapper.timesInt64#
|
580
|
595
|
, testPrimopDivLike "quotInt64#" Primop.quotInt64# Wrapper.quotInt64#
|
581
|
596
|
, testPrimopDivLike "remInt64#" Primop.remInt64# Wrapper.remInt64#
|
582
|
|
- , testPrimop "uncheckedIShiftL64#" Primop.uncheckedIShiftL64# Wrapper.uncheckedIShiftL64#
|
583
|
|
- , testPrimop "uncheckedIShiftRA64#" Primop.uncheckedIShiftRA64# Wrapper.uncheckedIShiftRA64#
|
584
|
|
- , testPrimop "uncheckedIShiftRL64#" Primop.uncheckedIShiftRL64# Wrapper.uncheckedIShiftRL64#
|
|
597
|
+ , testPrimopShift "uncheckedIShiftL64#" Primop.uncheckedIShiftL64# Wrapper.uncheckedIShiftL64#
|
|
598
|
+ , testPrimopShift "uncheckedIShiftRA64#" Primop.uncheckedIShiftRA64# Wrapper.uncheckedIShiftRA64#
|
|
599
|
+ , testPrimopShift "uncheckedIShiftRL64#" Primop.uncheckedIShiftRL64# Wrapper.uncheckedIShiftRL64#
|
585
|
600
|
, testPrimop "int64ToWord64#" Primop.int64ToWord64# Wrapper.int64ToWord64#
|
586
|
601
|
, testPrimop "eqInt64#" Primop.eqInt64# Wrapper.eqInt64#
|
587
|
602
|
, testPrimop "geInt64#" Primop.geInt64# Wrapper.geInt64#
|
... |
... |
@@ -600,8 +615,8 @@ testPrimops = Group "primop" |
600
|
615
|
, testPrimop "or64#" Primop.or64# Wrapper.or64#
|
601
|
616
|
, testPrimop "xor64#" Primop.xor64# Wrapper.xor64#
|
602
|
617
|
, testPrimop "not64#" Primop.not64# Wrapper.not64#
|
603
|
|
- , testPrimop "uncheckedShiftL64#" Primop.uncheckedShiftL64# Wrapper.uncheckedShiftL64#
|
604
|
|
- , testPrimop "uncheckedShiftRL64#" Primop.uncheckedShiftRL64# Wrapper.uncheckedShiftRL64#
|
|
618
|
+ , testPrimopShift "uncheckedShiftL64#" Primop.uncheckedShiftL64# Wrapper.uncheckedShiftL64#
|
|
619
|
+ , testPrimopShift "uncheckedShiftRL64#" Primop.uncheckedShiftRL64# Wrapper.uncheckedShiftRL64#
|
605
|
620
|
, testPrimop "word64ToInt64#" Primop.word64ToInt64# Wrapper.word64ToInt64#
|
606
|
621
|
, testPrimop "eqWord64#" Primop.eqWord64# Wrapper.eqWord64#
|
607
|
622
|
, testPrimop "geWord64#" Primop.geWord64# Wrapper.geWord64#
|
... |
... |
@@ -632,9 +647,9 @@ testPrimops = Group "primop" |
632
|
647
|
, testPrimop "<=#" (Primop.<=#) (Wrapper.<=#)
|
633
|
648
|
, testPrimop "chr#" Primop.chr# Wrapper.chr#
|
634
|
649
|
, testPrimop "int2Word#" Primop.int2Word# Wrapper.int2Word#
|
635
|
|
- , testPrimop "uncheckedIShiftL#" Primop.uncheckedIShiftL# Wrapper.uncheckedIShiftL#
|
636
|
|
- , testPrimop "uncheckedIShiftRA#" Primop.uncheckedIShiftRA# Wrapper.uncheckedIShiftRA#
|
637
|
|
- , testPrimop "uncheckedIShiftRL#" Primop.uncheckedIShiftRL# Wrapper.uncheckedIShiftRL#
|
|
650
|
+ , testPrimopShift "uncheckedIShiftL#" Primop.uncheckedIShiftL# Wrapper.uncheckedIShiftL#
|
|
651
|
+ , testPrimopShift "uncheckedIShiftRA#" Primop.uncheckedIShiftRA# Wrapper.uncheckedIShiftRA#
|
|
652
|
+ , testPrimopShift "uncheckedIShiftRL#" Primop.uncheckedIShiftRL# Wrapper.uncheckedIShiftRL#
|
638
|
653
|
, testPrimop "plusWord#" Primop.plusWord# Wrapper.plusWord#
|
639
|
654
|
, testPrimop "addWordC#" Primop.addWordC# Wrapper.addWordC#
|
640
|
655
|
, testPrimop "subWordC#" Primop.subWordC# Wrapper.subWordC#
|
... |
... |
@@ -649,8 +664,8 @@ testPrimops = Group "primop" |
649
|
664
|
, testPrimop "or#" Primop.or# Wrapper.or#
|
650
|
665
|
, testPrimop "xor#" Primop.xor# Wrapper.xor#
|
651
|
666
|
, testPrimop "not#" Primop.not# Wrapper.not#
|
652
|
|
- , testPrimop "uncheckedShiftL#" Primop.uncheckedShiftL# Wrapper.uncheckedShiftL#
|
653
|
|
- , testPrimop "uncheckedShiftRL#" Primop.uncheckedShiftRL# Wrapper.uncheckedShiftRL#
|
|
667
|
+ , testPrimopShift "uncheckedShiftL#" Primop.uncheckedShiftL# Wrapper.uncheckedShiftL#
|
|
668
|
+ , testPrimopShift "uncheckedShiftRL#" Primop.uncheckedShiftRL# Wrapper.uncheckedShiftRL#
|
654
|
669
|
, testPrimop "word2Int#" Primop.word2Int# Wrapper.word2Int#
|
655
|
670
|
, testPrimop "gtWord#" Primop.gtWord# Wrapper.gtWord#
|
656
|
671
|
, testPrimop "geWord#" Primop.geWord# Wrapper.geWord#
|
... |
... |
@@ -709,6 +724,7 @@ instance TestPrimop (Char# -> Int#) where |
709
|
724
|
instance TestPrimop (Int# -> Int# -> Int#) where
|
710
|
725
|
testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
711
|
726
|
testPrimopDivLike s l r = Property s $ twoNonZero $ \ (uInt#-> x0) (uInt#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
|
727
|
+ testPrimopShift s l r = Property s $ \ (uInt#-> x0) (BoundedShiftAmount @Int shift) -> wInt# (l x0 (uInt# shift)) === wInt# (r x0 (uInt# shift))
|
712
|
728
|
|
713
|
729
|
instance TestPrimop (Int# -> Int# -> (# Int#,Int# #)) where
|
714
|
730
|
testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> WTUP2(wInt#,wInt#, (l x0 x1)) === WTUP2(wInt#,wInt#, (r x0 x1))
|
... |
... |
@@ -741,6 +757,7 @@ instance TestPrimop (Int# -> Word#) where |
741
|
757
|
|
742
|
758
|
instance TestPrimop (Int16# -> Int# -> Int16#) where
|
743
|
759
|
testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt#-> x1) -> wInt16# (l x0 x1) === wInt16# (r x0 x1)
|
|
760
|
+ testPrimopShift s l r = Property s $ \ (uInt16#-> x0) (BoundedShiftAmount @Int16 shift) -> wInt16# (l x0 (uInt# shift)) === wInt16# (r x0 (uInt# shift))
|
744
|
761
|
|
745
|
762
|
instance TestPrimop (Int16# -> Int16# -> Int#) where
|
746
|
763
|
testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt16#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -765,6 +782,7 @@ instance TestPrimop (Int16# -> Word16#) where |
765
|
782
|
|
766
|
783
|
instance TestPrimop (Int32# -> Int# -> Int32#) where
|
767
|
784
|
testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt#-> x1) -> wInt32# (l x0 x1) === wInt32# (r x0 x1)
|
|
785
|
+ testPrimopShift s l r = Property s $ \ (uInt32#-> x0) (BoundedShiftAmount @Int32 shift) -> wInt32# (l x0 (uInt# shift)) === wInt32# (r x0 (uInt# shift))
|
768
|
786
|
|
769
|
787
|
instance TestPrimop (Int32# -> Int32# -> Int#) where
|
770
|
788
|
testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt32#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -789,6 +807,7 @@ instance TestPrimop (Int32# -> Word32#) where |
789
|
807
|
|
790
|
808
|
instance TestPrimop (Int64# -> Int# -> Int64#) where
|
791
|
809
|
testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt#-> x1) -> wInt64# (l x0 x1) === wInt64# (r x0 x1)
|
|
810
|
+ testPrimopShift s l r = Property s $ \ (uInt64#-> x0) (BoundedShiftAmount @Int64 shift) -> wInt64# (l x0 (uInt# shift)) === wInt64# (r x0 (uInt# shift))
|
792
|
811
|
|
793
|
812
|
instance TestPrimop (Int64# -> Int64# -> Int#) where
|
794
|
813
|
testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt64#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -809,6 +828,7 @@ instance TestPrimop (Int64# -> Word64#) where |
809
|
828
|
|
810
|
829
|
instance TestPrimop (Int8# -> Int# -> Int8#) where
|
811
|
830
|
testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt#-> x1) -> wInt8# (l x0 x1) === wInt8# (r x0 x1)
|
|
831
|
+ testPrimopShift s l r = Property s $ \ (uInt8#-> x0) (BoundedShiftAmount @Int8 shift) -> wInt8# (l x0 (uInt# shift)) === wInt8# (r x0 (uInt# shift))
|
812
|
832
|
|
813
|
833
|
instance TestPrimop (Int8# -> Int8# -> Int#) where
|
814
|
834
|
testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt8#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -833,6 +853,7 @@ instance TestPrimop (Int8# -> Word8#) where |
833
|
853
|
|
834
|
854
|
instance TestPrimop (Word# -> Int# -> Word#) where
|
835
|
855
|
testPrimop s l r = Property s $ \ (uWord#-> x0) (uInt#-> x1) -> wWord# (l x0 x1) === wWord# (r x0 x1)
|
|
856
|
+ testPrimopShift s l r = Property s $ \ (uWord#-> x0) (BoundedShiftAmount @Word shift) -> wWord# (l x0 (uInt# shift)) === wWord# (r x0 (uInt# shift))
|
836
|
857
|
|
837
|
858
|
instance TestPrimop (Word# -> Word# -> Int#) where
|
838
|
859
|
testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -870,6 +891,7 @@ instance TestPrimop (Word# -> Word8#) where |
870
|
891
|
|
871
|
892
|
instance TestPrimop (Word16# -> Int# -> Word16#) where
|
872
|
893
|
testPrimop s l r = Property s $ \ (uWord16#-> x0) (uInt#-> x1) -> wWord16# (l x0 x1) === wWord16# (r x0 x1)
|
|
894
|
+ testPrimopShift s l r = Property s $ \ (uWord16#-> x0) (BoundedShiftAmount @Word16 shift) -> wWord16# (l x0 (uInt# shift)) === wWord16# (r x0 (uInt# shift))
|
873
|
895
|
|
874
|
896
|
instance TestPrimop (Word16# -> Word16# -> Int#) where
|
875
|
897
|
testPrimop s l r = Property s $ \ (uWord16#-> x0) (uWord16#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -894,6 +916,7 @@ instance TestPrimop (Word16# -> Word16#) where |
894
|
916
|
|
895
|
917
|
instance TestPrimop (Word32# -> Int# -> Word32#) where
|
896
|
918
|
testPrimop s l r = Property s $ \ (uWord32#-> x0) (uInt#-> x1) -> wWord32# (l x0 x1) === wWord32# (r x0 x1)
|
|
919
|
+ testPrimopShift s l r = Property s $ \ (uWord32#-> x0) (BoundedShiftAmount @Word32 shift) -> wWord32# (l x0 (uInt# shift)) === wWord32# (r x0 (uInt# shift))
|
897
|
920
|
|
898
|
921
|
instance TestPrimop (Word32# -> Word32# -> Int#) where
|
899
|
922
|
testPrimop s l r = Property s $ \ (uWord32#-> x0) (uWord32#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -918,6 +941,7 @@ instance TestPrimop (Word32# -> Word32#) where |
918
|
941
|
|
919
|
942
|
instance TestPrimop (Word64# -> Int# -> Word64#) where
|
920
|
943
|
testPrimop s l r = Property s $ \ (uWord64#-> x0) (uInt#-> x1) -> wWord64# (l x0 x1) === wWord64# (r x0 x1)
|
|
944
|
+ testPrimopShift s l r = Property s $ \ (uWord64#-> x0) (BoundedShiftAmount @Word64 shift) -> wWord64# (l x0 (uInt# shift)) === wWord64# (r x0 (uInt# shift))
|
921
|
945
|
|
922
|
946
|
instance TestPrimop (Word64# -> Word64# -> Int#) where
|
923
|
947
|
testPrimop s l r = Property s $ \ (uWord64#-> x0) (uWord64#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -938,6 +962,7 @@ instance TestPrimop (Word64# -> Word64#) where |
938
|
962
|
|
939
|
963
|
instance TestPrimop (Word8# -> Int# -> Word8#) where
|
940
|
964
|
testPrimop s l r = Property s $ \ (uWord8#-> x0) (uInt#-> x1) -> wWord8# (l x0 x1) === wWord8# (r x0 x1)
|
|
965
|
+ testPrimopShift s l r = Property s $ \ (uWord8#-> x0) (BoundedShiftAmount @Word8 shift) -> wWord8# (l x0 (uInt# shift)) === wWord8# (r x0 (uInt# shift))
|
941
|
966
|
|
942
|
967
|
instance TestPrimop (Word8# -> Word8# -> Int#) where
|
943
|
968
|
testPrimop s l r = Property s $ \ (uWord8#-> x0) (uWord8#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|