... |
... |
@@ -24,7 +24,7 @@ module Main |
24
|
24
|
( main
|
25
|
25
|
) where
|
26
|
26
|
|
27
|
|
-import Data.Bits (Bits((.&.), bit))
|
|
27
|
+import Data.Bits (Bits((.&.), bit), finiteBitSize)
|
28
|
28
|
import Data.Word
|
29
|
29
|
import Data.Int
|
30
|
30
|
import GHC.Natural
|
... |
... |
@@ -133,6 +133,52 @@ newtype NonZero a = NonZero { getNonZero :: a } |
133
|
133
|
instance (Arbitrary a, Num a, Eq a) => Arbitrary (NonZero a) where
|
134
|
134
|
arbitrary = nonZero
|
135
|
135
|
|
|
136
|
+-- | A newtype for shift amounts that are bounded by word size
|
|
137
|
+newtype BoundedShift a = BoundedShift { getBoundedShift :: Int }
|
|
138
|
+ deriving (Eq,Ord,Show)
|
|
139
|
+
|
|
140
|
+-- | Generate shift amounts bounded by the word size for each type
|
|
141
|
+boundedShift8 :: Gen (BoundedShift Int8)
|
|
142
|
+boundedShift8 = do
|
|
143
|
+ x <- arbitrary
|
|
144
|
+ return $ BoundedShift (abs x `mod` 8)
|
|
145
|
+
|
|
146
|
+boundedShift16 :: Gen (BoundedShift Int16)
|
|
147
|
+boundedShift16 = do
|
|
148
|
+ x <- arbitrary
|
|
149
|
+ return $ BoundedShift (abs x `mod` 16)
|
|
150
|
+
|
|
151
|
+boundedShift32 :: Gen (BoundedShift Int32)
|
|
152
|
+boundedShift32 = do
|
|
153
|
+ x <- arbitrary
|
|
154
|
+ return $ BoundedShift (abs x `mod` 32)
|
|
155
|
+
|
|
156
|
+boundedShift64 :: Gen (BoundedShift Int64)
|
|
157
|
+boundedShift64 = do
|
|
158
|
+ x <- arbitrary
|
|
159
|
+ return $ BoundedShift (abs x `mod` 64)
|
|
160
|
+
|
|
161
|
+boundedShiftWord :: Gen (BoundedShift Int)
|
|
162
|
+boundedShiftWord = do
|
|
163
|
+ x <- arbitrary
|
|
164
|
+ return $ BoundedShift (abs x `mod` finiteBitSize (undefined :: Word))
|
|
165
|
+
|
|
166
|
+-- Arbitrary instances for BoundedShift types to work with lambda patterns
|
|
167
|
+instance Arbitrary (BoundedShift Int8) where
|
|
168
|
+ arbitrary = boundedShift8
|
|
169
|
+
|
|
170
|
+instance Arbitrary (BoundedShift Int16) where
|
|
171
|
+ arbitrary = boundedShift16
|
|
172
|
+
|
|
173
|
+instance Arbitrary (BoundedShift Int32) where
|
|
174
|
+ arbitrary = boundedShift32
|
|
175
|
+
|
|
176
|
+instance Arbitrary (BoundedShift Int64) where
|
|
177
|
+ arbitrary = boundedShift64
|
|
178
|
+
|
|
179
|
+instance Arbitrary (BoundedShift Int) where
|
|
180
|
+ arbitrary = boundedShiftWord
|
|
181
|
+
|
136
|
182
|
instance Arbitrary Natural where
|
137
|
183
|
arbitrary = integralDownsize . (`mod` 10000) . abs <$> arbitraryInt64
|
138
|
184
|
|
... |
... |
@@ -395,6 +441,10 @@ class TestPrimop f where |
395
|
441
|
testPrimopDivLike :: String -> f -> f -> Test
|
396
|
442
|
testPrimopDivLike _ _ _ = error "Div testing not supported for this type."
|
397
|
443
|
|
|
444
|
+ -- | Special test method for shift operations that bounds the shift amount
|
|
445
|
+ testPrimopShift :: String -> f -> f -> Test
|
|
446
|
+ testPrimopShift _ _ _ = error "Shift testing not supported for this type."
|
|
447
|
+
|
398
|
448
|
{-
|
399
|
449
|
instance TestPrimop (Int# -> Int# -> Int#) where
|
400
|
450
|
testPrimop s l r = Property s $ \(uInt -> a1) (uInt -> a2) -> (wInt (l a1 a2)) === wInt (r a1 a2)
|
... |
... |
@@ -460,9 +510,9 @@ testPrimops = Group "primop" |
460
|
510
|
, testPrimopDivLike "quotInt8#" Primop.quotInt8# Wrapper.quotInt8#
|
461
|
511
|
, testPrimopDivLike "remInt8#" Primop.remInt8# Wrapper.remInt8#
|
462
|
512
|
, 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#
|
|
513
|
+ , testPrimopShift "uncheckedShiftLInt8#" Primop.uncheckedShiftLInt8# Wrapper.uncheckedShiftLInt8#
|
|
514
|
+ , testPrimopShift "uncheckedShiftRAInt8#" Primop.uncheckedShiftRAInt8# Wrapper.uncheckedShiftRAInt8#
|
|
515
|
+ , testPrimopShift "uncheckedShiftRLInt8#" Primop.uncheckedShiftRLInt8# Wrapper.uncheckedShiftRLInt8#
|
466
|
516
|
, testPrimop "int8ToWord8#" Primop.int8ToWord8# Wrapper.int8ToWord8#
|
467
|
517
|
, testPrimop "eqInt8#" Primop.eqInt8# Wrapper.eqInt8#
|
468
|
518
|
, testPrimop "geInt8#" Primop.geInt8# Wrapper.geInt8#
|
... |
... |
@@ -482,8 +532,8 @@ testPrimops = Group "primop" |
482
|
532
|
, testPrimop "orWord8#" Primop.orWord8# Wrapper.orWord8#
|
483
|
533
|
, testPrimop "xorWord8#" Primop.xorWord8# Wrapper.xorWord8#
|
484
|
534
|
, testPrimop "notWord8#" Primop.notWord8# Wrapper.notWord8#
|
485
|
|
- , testPrimop "uncheckedShiftLWord8#" Primop.uncheckedShiftLWord8# Wrapper.uncheckedShiftLWord8#
|
486
|
|
- , testPrimop "uncheckedShiftRLWord8#" Primop.uncheckedShiftRLWord8# Wrapper.uncheckedShiftRLWord8#
|
|
535
|
+ , testPrimopShift "uncheckedShiftLWord8#" Primop.uncheckedShiftLWord8# Wrapper.uncheckedShiftLWord8#
|
|
536
|
+ , testPrimopShift "uncheckedShiftRLWord8#" Primop.uncheckedShiftRLWord8# Wrapper.uncheckedShiftRLWord8#
|
487
|
537
|
, testPrimop "word8ToInt8#" Primop.word8ToInt8# Wrapper.word8ToInt8#
|
488
|
538
|
, testPrimop "eqWord8#" Primop.eqWord8# Wrapper.eqWord8#
|
489
|
539
|
, testPrimop "geWord8#" Primop.geWord8# Wrapper.geWord8#
|
... |
... |
@@ -500,9 +550,9 @@ testPrimops = Group "primop" |
500
|
550
|
, testPrimopDivLike "quotInt16#" Primop.quotInt16# Wrapper.quotInt16#
|
501
|
551
|
, testPrimopDivLike "remInt16#" Primop.remInt16# Wrapper.remInt16#
|
502
|
552
|
, 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#
|
|
553
|
+ , testPrimopShift "uncheckedShiftLInt16#" Primop.uncheckedShiftLInt16# Wrapper.uncheckedShiftLInt16#
|
|
554
|
+ , testPrimopShift "uncheckedShiftRAInt16#" Primop.uncheckedShiftRAInt16# Wrapper.uncheckedShiftRAInt16#
|
|
555
|
+ , testPrimopShift "uncheckedShiftRLInt16#" Primop.uncheckedShiftRLInt16# Wrapper.uncheckedShiftRLInt16#
|
506
|
556
|
, testPrimop "int16ToWord16#" Primop.int16ToWord16# Wrapper.int16ToWord16#
|
507
|
557
|
, testPrimop "eqInt16#" Primop.eqInt16# Wrapper.eqInt16#
|
508
|
558
|
, testPrimop "geInt16#" Primop.geInt16# Wrapper.geInt16#
|
... |
... |
@@ -522,8 +572,8 @@ testPrimops = Group "primop" |
522
|
572
|
, testPrimop "orWord16#" Primop.orWord16# Wrapper.orWord16#
|
523
|
573
|
, testPrimop "xorWord16#" Primop.xorWord16# Wrapper.xorWord16#
|
524
|
574
|
, testPrimop "notWord16#" Primop.notWord16# Wrapper.notWord16#
|
525
|
|
- , testPrimop "uncheckedShiftLWord16#" Primop.uncheckedShiftLWord16# Wrapper.uncheckedShiftLWord16#
|
526
|
|
- , testPrimop "uncheckedShiftRLWord16#" Primop.uncheckedShiftRLWord16# Wrapper.uncheckedShiftRLWord16#
|
|
575
|
+ , testPrimopShift "uncheckedShiftLWord16#" Primop.uncheckedShiftLWord16# Wrapper.uncheckedShiftLWord16#
|
|
576
|
+ , testPrimopShift "uncheckedShiftRLWord16#" Primop.uncheckedShiftRLWord16# Wrapper.uncheckedShiftRLWord16#
|
527
|
577
|
, testPrimop "word16ToInt16#" Primop.word16ToInt16# Wrapper.word16ToInt16#
|
528
|
578
|
, testPrimop "eqWord16#" Primop.eqWord16# Wrapper.eqWord16#
|
529
|
579
|
, testPrimop "geWord16#" Primop.geWord16# Wrapper.geWord16#
|
... |
... |
@@ -540,9 +590,9 @@ testPrimops = Group "primop" |
540
|
590
|
, testPrimopDivLike "quotInt32#" Primop.quotInt32# Wrapper.quotInt32#
|
541
|
591
|
, testPrimopDivLike "remInt32#" Primop.remInt32# Wrapper.remInt32#
|
542
|
592
|
, 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#
|
|
593
|
+ , testPrimopShift "uncheckedShiftLInt32#" Primop.uncheckedShiftLInt32# Wrapper.uncheckedShiftLInt32#
|
|
594
|
+ , testPrimopShift "uncheckedShiftRAInt32#" Primop.uncheckedShiftRAInt32# Wrapper.uncheckedShiftRAInt32#
|
|
595
|
+ , testPrimopShift "uncheckedShiftRLInt32#" Primop.uncheckedShiftRLInt32# Wrapper.uncheckedShiftRLInt32#
|
546
|
596
|
, testPrimop "int32ToWord32#" Primop.int32ToWord32# Wrapper.int32ToWord32#
|
547
|
597
|
, testPrimop "eqInt32#" Primop.eqInt32# Wrapper.eqInt32#
|
548
|
598
|
, testPrimop "geInt32#" Primop.geInt32# Wrapper.geInt32#
|
... |
... |
@@ -562,8 +612,8 @@ testPrimops = Group "primop" |
562
|
612
|
, testPrimop "orWord32#" Primop.orWord32# Wrapper.orWord32#
|
563
|
613
|
, testPrimop "xorWord32#" Primop.xorWord32# Wrapper.xorWord32#
|
564
|
614
|
, testPrimop "notWord32#" Primop.notWord32# Wrapper.notWord32#
|
565
|
|
- , testPrimop "uncheckedShiftLWord32#" Primop.uncheckedShiftLWord32# Wrapper.uncheckedShiftLWord32#
|
566
|
|
- , testPrimop "uncheckedShiftRLWord32#" Primop.uncheckedShiftRLWord32# Wrapper.uncheckedShiftRLWord32#
|
|
615
|
+ , testPrimopShift "uncheckedShiftLWord32#" Primop.uncheckedShiftLWord32# Wrapper.uncheckedShiftLWord32#
|
|
616
|
+ , testPrimopShift "uncheckedShiftRLWord32#" Primop.uncheckedShiftRLWord32# Wrapper.uncheckedShiftRLWord32#
|
567
|
617
|
, testPrimop "word32ToInt32#" Primop.word32ToInt32# Wrapper.word32ToInt32#
|
568
|
618
|
, testPrimop "eqWord32#" Primop.eqWord32# Wrapper.eqWord32#
|
569
|
619
|
, testPrimop "geWord32#" Primop.geWord32# Wrapper.geWord32#
|
... |
... |
@@ -579,9 +629,9 @@ testPrimops = Group "primop" |
579
|
629
|
, testPrimop "timesInt64#" Primop.timesInt64# Wrapper.timesInt64#
|
580
|
630
|
, testPrimopDivLike "quotInt64#" Primop.quotInt64# Wrapper.quotInt64#
|
581
|
631
|
, 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#
|
|
632
|
+ , testPrimopShift "uncheckedIShiftL64#" Primop.uncheckedIShiftL64# Wrapper.uncheckedIShiftL64#
|
|
633
|
+ , testPrimopShift "uncheckedIShiftRA64#" Primop.uncheckedIShiftRA64# Wrapper.uncheckedIShiftRA64#
|
|
634
|
+ , testPrimopShift "uncheckedIShiftRL64#" Primop.uncheckedIShiftRL64# Wrapper.uncheckedIShiftRL64#
|
585
|
635
|
, testPrimop "int64ToWord64#" Primop.int64ToWord64# Wrapper.int64ToWord64#
|
586
|
636
|
, testPrimop "eqInt64#" Primop.eqInt64# Wrapper.eqInt64#
|
587
|
637
|
, testPrimop "geInt64#" Primop.geInt64# Wrapper.geInt64#
|
... |
... |
@@ -600,8 +650,8 @@ testPrimops = Group "primop" |
600
|
650
|
, testPrimop "or64#" Primop.or64# Wrapper.or64#
|
601
|
651
|
, testPrimop "xor64#" Primop.xor64# Wrapper.xor64#
|
602
|
652
|
, testPrimop "not64#" Primop.not64# Wrapper.not64#
|
603
|
|
- , testPrimop "uncheckedShiftL64#" Primop.uncheckedShiftL64# Wrapper.uncheckedShiftL64#
|
604
|
|
- , testPrimop "uncheckedShiftRL64#" Primop.uncheckedShiftRL64# Wrapper.uncheckedShiftRL64#
|
|
653
|
+ , testPrimopShift "uncheckedShiftL64#" Primop.uncheckedShiftL64# Wrapper.uncheckedShiftL64#
|
|
654
|
+ , testPrimopShift "uncheckedShiftRL64#" Primop.uncheckedShiftRL64# Wrapper.uncheckedShiftRL64#
|
605
|
655
|
, testPrimop "word64ToInt64#" Primop.word64ToInt64# Wrapper.word64ToInt64#
|
606
|
656
|
, testPrimop "eqWord64#" Primop.eqWord64# Wrapper.eqWord64#
|
607
|
657
|
, testPrimop "geWord64#" Primop.geWord64# Wrapper.geWord64#
|
... |
... |
@@ -632,9 +682,9 @@ testPrimops = Group "primop" |
632
|
682
|
, testPrimop "<=#" (Primop.<=#) (Wrapper.<=#)
|
633
|
683
|
, testPrimop "chr#" Primop.chr# Wrapper.chr#
|
634
|
684
|
, 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#
|
|
685
|
+ , testPrimopShift "uncheckedIShiftL#" Primop.uncheckedIShiftL# Wrapper.uncheckedIShiftL#
|
|
686
|
+ , testPrimopShift "uncheckedIShiftRA#" Primop.uncheckedIShiftRA# Wrapper.uncheckedIShiftRA#
|
|
687
|
+ , testPrimopShift "uncheckedIShiftRL#" Primop.uncheckedIShiftRL# Wrapper.uncheckedIShiftRL#
|
638
|
688
|
, testPrimop "plusWord#" Primop.plusWord# Wrapper.plusWord#
|
639
|
689
|
, testPrimop "addWordC#" Primop.addWordC# Wrapper.addWordC#
|
640
|
690
|
, testPrimop "subWordC#" Primop.subWordC# Wrapper.subWordC#
|
... |
... |
@@ -649,8 +699,8 @@ testPrimops = Group "primop" |
649
|
699
|
, testPrimop "or#" Primop.or# Wrapper.or#
|
650
|
700
|
, testPrimop "xor#" Primop.xor# Wrapper.xor#
|
651
|
701
|
, testPrimop "not#" Primop.not# Wrapper.not#
|
652
|
|
- , testPrimop "uncheckedShiftL#" Primop.uncheckedShiftL# Wrapper.uncheckedShiftL#
|
653
|
|
- , testPrimop "uncheckedShiftRL#" Primop.uncheckedShiftRL# Wrapper.uncheckedShiftRL#
|
|
702
|
+ , testPrimopShift "uncheckedShiftL#" Primop.uncheckedShiftL# Wrapper.uncheckedShiftL#
|
|
703
|
+ , testPrimopShift "uncheckedShiftRL#" Primop.uncheckedShiftRL# Wrapper.uncheckedShiftRL#
|
654
|
704
|
, testPrimop "word2Int#" Primop.word2Int# Wrapper.word2Int#
|
655
|
705
|
, testPrimop "gtWord#" Primop.gtWord# Wrapper.gtWord#
|
656
|
706
|
, testPrimop "geWord#" Primop.geWord# Wrapper.geWord#
|
... |
... |
@@ -709,6 +759,7 @@ instance TestPrimop (Char# -> Int#) where |
709
|
759
|
instance TestPrimop (Int# -> Int# -> Int#) where
|
710
|
760
|
testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
711
|
761
|
testPrimopDivLike s l r = Property s $ twoNonZero $ \ (uInt#-> x0) (uInt#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
|
762
|
+ testPrimopShift s l r = Property s $ \ (uInt#-> x0) (BoundedShift shift :: BoundedShift Int) -> wInt# (l x0 (uInt# shift)) === wInt# (r x0 (uInt# shift))
|
712
|
763
|
|
713
|
764
|
instance TestPrimop (Int# -> Int# -> (# Int#,Int# #)) where
|
714
|
765
|
testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> WTUP2(wInt#,wInt#, (l x0 x1)) === WTUP2(wInt#,wInt#, (r x0 x1))
|
... |
... |
@@ -741,6 +792,7 @@ instance TestPrimop (Int# -> Word#) where |
741
|
792
|
|
742
|
793
|
instance TestPrimop (Int16# -> Int# -> Int16#) where
|
743
|
794
|
testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt#-> x1) -> wInt16# (l x0 x1) === wInt16# (r x0 x1)
|
|
795
|
+ testPrimopShift s l r = Property s $ \ (uInt16#-> x0) (BoundedShift shift :: BoundedShift Int16) -> wInt16# (l x0 (uInt# shift)) === wInt16# (r x0 (uInt# shift))
|
744
|
796
|
|
745
|
797
|
instance TestPrimop (Int16# -> Int16# -> Int#) where
|
746
|
798
|
testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt16#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -765,6 +817,7 @@ instance TestPrimop (Int16# -> Word16#) where |
765
|
817
|
|
766
|
818
|
instance TestPrimop (Int32# -> Int# -> Int32#) where
|
767
|
819
|
testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt#-> x1) -> wInt32# (l x0 x1) === wInt32# (r x0 x1)
|
|
820
|
+ testPrimopShift s l r = Property s $ \ (uInt32#-> x0) (BoundedShift shift :: BoundedShift Int32) -> wInt32# (l x0 (uInt# shift)) === wInt32# (r x0 (uInt# shift))
|
768
|
821
|
|
769
|
822
|
instance TestPrimop (Int32# -> Int32# -> Int#) where
|
770
|
823
|
testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt32#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -789,6 +842,7 @@ instance TestPrimop (Int32# -> Word32#) where |
789
|
842
|
|
790
|
843
|
instance TestPrimop (Int64# -> Int# -> Int64#) where
|
791
|
844
|
testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt#-> x1) -> wInt64# (l x0 x1) === wInt64# (r x0 x1)
|
|
845
|
+ testPrimopShift s l r = Property s $ \ (uInt64#-> x0) (BoundedShift shift :: BoundedShift Int64) -> wInt64# (l x0 (uInt# shift)) === wInt64# (r x0 (uInt# shift))
|
792
|
846
|
|
793
|
847
|
instance TestPrimop (Int64# -> Int64# -> Int#) where
|
794
|
848
|
testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt64#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -809,6 +863,7 @@ instance TestPrimop (Int64# -> Word64#) where |
809
|
863
|
|
810
|
864
|
instance TestPrimop (Int8# -> Int# -> Int8#) where
|
811
|
865
|
testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt#-> x1) -> wInt8# (l x0 x1) === wInt8# (r x0 x1)
|
|
866
|
+ testPrimopShift s l r = Property s $ \ (uInt8#-> x0) (BoundedShift shift :: BoundedShift Int8) -> wInt8# (l x0 (uInt# shift)) === wInt8# (r x0 (uInt# shift))
|
812
|
867
|
|
813
|
868
|
instance TestPrimop (Int8# -> Int8# -> Int#) where
|
814
|
869
|
testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt8#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -833,6 +888,7 @@ instance TestPrimop (Int8# -> Word8#) where |
833
|
888
|
|
834
|
889
|
instance TestPrimop (Word# -> Int# -> Word#) where
|
835
|
890
|
testPrimop s l r = Property s $ \ (uWord#-> x0) (uInt#-> x1) -> wWord# (l x0 x1) === wWord# (r x0 x1)
|
|
891
|
+ testPrimopShift s l r = Property s $ \ (uWord#-> x0) (BoundedShift shift :: BoundedShift Int) -> wWord# (l x0 (uInt# shift)) === wWord# (r x0 (uInt# shift))
|
836
|
892
|
|
837
|
893
|
instance TestPrimop (Word# -> Word# -> Int#) where
|
838
|
894
|
testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -870,6 +926,7 @@ instance TestPrimop (Word# -> Word8#) where |
870
|
926
|
|
871
|
927
|
instance TestPrimop (Word16# -> Int# -> Word16#) where
|
872
|
928
|
testPrimop s l r = Property s $ \ (uWord16#-> x0) (uInt#-> x1) -> wWord16# (l x0 x1) === wWord16# (r x0 x1)
|
|
929
|
+ testPrimopShift s l r = Property s $ \ (uWord16#-> x0) (BoundedShift shift :: BoundedShift Int16) -> wWord16# (l x0 (uInt# shift)) === wWord16# (r x0 (uInt# shift))
|
873
|
930
|
|
874
|
931
|
instance TestPrimop (Word16# -> Word16# -> Int#) where
|
875
|
932
|
testPrimop s l r = Property s $ \ (uWord16#-> x0) (uWord16#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -894,6 +951,7 @@ instance TestPrimop (Word16# -> Word16#) where |
894
|
951
|
|
895
|
952
|
instance TestPrimop (Word32# -> Int# -> Word32#) where
|
896
|
953
|
testPrimop s l r = Property s $ \ (uWord32#-> x0) (uInt#-> x1) -> wWord32# (l x0 x1) === wWord32# (r x0 x1)
|
|
954
|
+ testPrimopShift s l r = Property s $ \ (uWord32#-> x0) (BoundedShift shift :: BoundedShift Int32) -> wWord32# (l x0 (uInt# shift)) === wWord32# (r x0 (uInt# shift))
|
897
|
955
|
|
898
|
956
|
instance TestPrimop (Word32# -> Word32# -> Int#) where
|
899
|
957
|
testPrimop s l r = Property s $ \ (uWord32#-> x0) (uWord32#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -918,6 +976,7 @@ instance TestPrimop (Word32# -> Word32#) where |
918
|
976
|
|
919
|
977
|
instance TestPrimop (Word64# -> Int# -> Word64#) where
|
920
|
978
|
testPrimop s l r = Property s $ \ (uWord64#-> x0) (uInt#-> x1) -> wWord64# (l x0 x1) === wWord64# (r x0 x1)
|
|
979
|
+ testPrimopShift s l r = Property s $ \ (uWord64#-> x0) (BoundedShift shift :: BoundedShift Int64) -> wWord64# (l x0 (uInt# shift)) === wWord64# (r x0 (uInt# shift))
|
921
|
980
|
|
922
|
981
|
instance TestPrimop (Word64# -> Word64# -> Int#) where
|
923
|
982
|
testPrimop s l r = Property s $ \ (uWord64#-> x0) (uWord64#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|
... |
... |
@@ -938,6 +997,7 @@ instance TestPrimop (Word64# -> Word64#) where |
938
|
997
|
|
939
|
998
|
instance TestPrimop (Word8# -> Int# -> Word8#) where
|
940
|
999
|
testPrimop s l r = Property s $ \ (uWord8#-> x0) (uInt#-> x1) -> wWord8# (l x0 x1) === wWord8# (r x0 x1)
|
|
1000
|
+ testPrimopShift s l r = Property s $ \ (uWord8#-> x0) (BoundedShift shift :: BoundedShift Int8) -> wWord8# (l x0 (uInt# shift)) === wWord8# (r x0 (uInt# shift))
|
941
|
1001
|
|
942
|
1002
|
instance TestPrimop (Word8# -> Word8# -> Int#) where
|
943
|
1003
|
testPrimop s l r = Property s $ \ (uWord8#-> x0) (uWord8#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
|