[Git][ghc/ghc][wip/andreask/interpreter_primops] Compare compiled primop vs interpreted primop test

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Tue Feb 25 11:57:00 UTC 2025



Matthew Pickering pushed to branch wip/andreask/interpreter_primops at Glasgow Haskell Compiler / GHC


Commits:
a10aa396 by Matthew Pickering at 2025-02-25T11:56:29+00:00
Compare compiled primop vs interpreted primop test

- - - - -


4 changed files:

- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs


Changes:

=====================================
testsuite/tests/numeric/should_run/foundation.hs
=====================================
@@ -5,6 +5,9 @@
 {-# LANGUAGE DerivingStrategies #-}
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE UnboxedTuples #-}
 module Main
     ( main
     ) where
@@ -26,6 +29,13 @@ import Foreign.Ptr
 import Data.List (intercalate)
 import Data.IORef
 import Unsafe.Coerce
+import GHC.Types
+import Data.Char
+import Data.Semigroup
+import System.Exit
+
+import qualified GHC.Internal.PrimopWrappers as Wrapper
+import qualified GHC.Internal.Prim as Primop
 
 newtype Gen a = Gen { runGen :: (ReaderT LCGGen IO a) }
   deriving newtype (Functor, Applicative, Monad)
@@ -126,6 +136,13 @@ instance Arbitrary Int16 where
 instance Arbitrary Int8 where
     arbitrary = integralDownsize <$> arbitraryInt64
 
+instance Arbitrary Char where
+    arbitrary = do
+      let low = fromEnum (minBound :: Char)
+          high = fromEnum (maxBound :: Char)
+      x <- arbitrary
+      if x >= low && x <= high then return (chr x) else arbitrary
+
 int64ToInt :: Int64 -> Int
 int64ToInt (I64# i) = I# (int64ToInt# i)
 
@@ -134,7 +151,7 @@ word64ToWord :: Word64 -> Word
 word64ToWord (W64# i) = W# (word64ToWord# i)
 
 
-data RunS = RunS { depth :: Int, rg :: LCGGen  }
+data RunS = RunS { depth :: Int, rg :: LCGGen, context :: [String] }
 
 newtype LCGGen = LCGGen { randomWord64 :: IO Word64 }
 
@@ -148,43 +165,75 @@ newLCGGen LCGParams{..}  = do
 
 
 runPropertyCheck (PropertyBinaryOp res desc s1 s2) =
-  if res then return True else (putMsg ("Failure: " ++ s1 ++ desc ++ s2) >> return False)
-runPropertyCheck (PropertyAnd a1 a2) = (&&) <$> runPropertyCheck a1 <*> runPropertyCheck a2
-
-runProperty :: Property -> ReaderT RunS IO ()
+  if res then return Success
+         else do
+          ctx <- context <$> ask
+          let msg = "Failure: " ++ s1 ++ desc ++ s2
+          putMsg msg
+          return (Failure [msg : ctx])
+runPropertyCheck (PropertyAnd a1 a2) = (<>) <$> runPropertyCheck a1 <*> runPropertyCheck a2
+
+runProperty :: Property -> ReaderT RunS IO Result
 runProperty (Prop p) = do
   let iterations = 100
   loop iterations iterations
   where
-    loop iterations 0 = putMsg ("Passed " ++ show iterations ++ " iterations")
+    loop iterations 0 = do
+      putMsg ("Passed " ++ show iterations ++ " iterations")
+      return Success
     loop iterations n = do
       h <- rg <$> ask
       p <- liftIO (runReaderT (runGen p) h)
       let (ss, pc) = getCheck p
       res <- runPropertyCheck pc
-      if res then loop iterations (n-1)
-             else putMsg ("With arguments " ++ intercalate ", " ss)
+      case res of
+        Success -> loop iterations (n-1)
+        Failure msgs -> do
+          let msg = ("With arguments " ++ intercalate ", " ss)
+          putMsg msg
+          return (Failure (map (msg :) msgs))
+
+data Result = Success | Failure [[String]]
+
+instance Semigroup Result where
+  Success <> x = x
+  x <> Success = x
+  (Failure xs) <> (Failure ys) = Failure (xs ++ ys)
+
+instance Monoid Result where
+  mempty = Success
 
 putMsg s = do
   n <- depth <$> ask
   liftIO . putStrLn $ replicate (n * 2) ' ' ++ s
 
-nest = local (\s -> s { depth = depth s + 1 })
 
-runTestInternal :: Test -> ReaderT RunS IO ()
+nest c = local (\s -> s { depth = depth s + 1, context = c : context s })
+
+runTestInternal :: Test -> ReaderT RunS IO Result
 runTestInternal (Group name tests) = do
-  putMsg ("Group " ++ name)
-  nest (mapM_ runTestInternal tests)
+  let label = ("Group " ++ name)
+  putMsg label
+  nest label (mconcat <$> mapM runTestInternal tests)
 runTestInternal (Property name p) = do
-  putMsg ("Running " ++ name)
-  nest $ runProperty (property p)
+  let label = ("Running " ++ name)
+  putMsg label
+  nest label $ runProperty (property p)
 
 
 runTests :: Test -> IO ()
 runTests t = do
   -- These params are the same ones as glibc uses.
   h <- newLCGGen (LCGParams { seed = 1238123213, m = 2^31, a = 1103515245, c = 12345 })
-  runReaderT  (runTestInternal t) (RunS 0 h)
+  res <- runReaderT  (runTestInternal t) (RunS 0 h [])
+  case res of
+    Success -> return ()
+    Failure tests -> do
+      putStrLn $ "These tests failed:  \n" ++ intercalate "  \n" (map (showStack 0 . reverse) tests)
+      exitFailure
+
+showStack _ [] = ""
+showStack n (s:ss) = replicate n ' ' ++ s ++ "\n" ++ showStack (n + 2) ss
 
 -------------------------------------------------------------------------------
 
@@ -272,6 +321,559 @@ testNumberRefs = Group "ALL"
     , testNumber "Word32" (Proxy :: Proxy Word32)
     , testNumber "Word64" (Proxy :: Proxy Word64)
     ]
+{-
+test_binop :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) a r'
+              (b :: TYPE r1) (r :: TYPE r2)  . String   -> (a -> b) -> (r -> r')
+                       -> (b -> b -> r)
+                       -> (b -> b -> r)
+                       -> Test
+test_binop name unwrap wrap primop wrapper =
+-}
+#define TEST_BINOP(name, unwrap, wrap, primop, wrapper)  Property name $ \l r -> wrap (primop (unwrap l) (unwrap r)) === wrap (wrapper (unwrap l) (unwrap r))
+
+wInt# :: Int# -> Int
+wInt# = I#
+
+uInt# :: Int -> Int#
+uInt# (I# x) = x
+
+wWord#:: Word# -> Word
+wWord#= W#
+
+uWord# (W# w) = w
+uWord8# (W8# w) = w
+uWord16# (W16# w) = w
+uWord32# (W32# w) = w
+uWord64# (W64# w) = w
+uChar# (C# c) = c
+uInt8# (I8# w) = w
+uInt16# (I16# w) = w
+uInt32# (I32# w) = w
+uInt64# (I64# w) = w
+
+wWord8# = W8#
+wWord16# = W16#
+wWord32# = W32#
+wWord64# = W64#
+wChar# = C#
+wInt8# = I8#
+wInt16# = I16#
+wInt32# = I32#
+wInt64# = I64#
+
+#define WTUP2(f, g, x) (case x of (# a, b #) -> (f a, g b))
+#define WTUP3(f, g, h, x) (case x of (# a, b, c #) -> (f a, g b, h c))
+
+
+class TestPrimop f where
+  testPrimop :: String -> f -> f -> Test
+
+{-
+instance TestPrimop (Int# -> Int# -> Int#) where
+  testPrimop s l r = Property s $ \(uInt -> a1) (uInt -> a2) -> (wInt (l a1 a2)) === wInt (r a1 a2)
+
+instance TestPrimop (Word# -> Word# -> Int#) where
+  testPrimop s l r = Property s $ \(uWord -> a1) (uWord -> a2) -> (wInt (l a1 a2)) === wInt (r a1 a2)
+
+instance TestPrimop (Word# -> Int#) where
+  testPrimop s l r = Property s $ \(uWord -> a1) -> (wInt (l a1)) === wInt (r a1)
+
+instance TestPrimop (Word# -> Int# -> Word#) where
+  testPrimop s l r = Property s $ \(uWord -> a1) (uInt -> a2) -> (wWord (l a1 a2)) === wWord (r a1 a2)
+  -}
+
+
+main = runTests (Group "ALL" [testNumberRefs, testPrimops])
+
+-- Test an interpreted primop vs a compiled primop
+testPrimops = Group "primop"
+  [ testPrimop "gtChar#" Primop.gtChar# Wrapper.gtChar#
+  , testPrimop "geChar#" Primop.geChar# Wrapper.geChar#
+  , testPrimop "eqChar#" Primop.eqChar# Wrapper.eqChar#
+  , testPrimop "neChar#" Primop.neChar# Wrapper.neChar#
+  , testPrimop "ltChar#" Primop.ltChar# Wrapper.ltChar#
+  , testPrimop "leChar#" Primop.leChar# Wrapper.leChar#
+  , testPrimop "ord#" Primop.ord# Wrapper.ord#
+  , testPrimop "int8ToInt#" Primop.int8ToInt# Wrapper.int8ToInt#
+  , testPrimop "intToInt8#" Primop.intToInt8# Wrapper.intToInt8#
+  , testPrimop "negateInt8#" Primop.negateInt8# Wrapper.negateInt8#
+  , testPrimop "plusInt8#" Primop.plusInt8# Wrapper.plusInt8#
+  , testPrimop "subInt8#" Primop.subInt8# Wrapper.subInt8#
+  , testPrimop "timesInt8#" Primop.timesInt8# Wrapper.timesInt8#
+  , testPrimop "quotInt8#" Primop.quotInt8# Wrapper.quotInt8#
+  , testPrimop "remInt8#" Primop.remInt8# Wrapper.remInt8#
+  , testPrimop "quotRemInt8#" Primop.quotRemInt8# Wrapper.quotRemInt8#
+  , testPrimop "uncheckedShiftLInt8#" Primop.uncheckedShiftLInt8# Wrapper.uncheckedShiftLInt8#
+  , testPrimop "uncheckedShiftRAInt8#" Primop.uncheckedShiftRAInt8# Wrapper.uncheckedShiftRAInt8#
+  , testPrimop "uncheckedShiftRLInt8#" Primop.uncheckedShiftRLInt8# Wrapper.uncheckedShiftRLInt8#
+  , testPrimop "int8ToWord8#" Primop.int8ToWord8# Wrapper.int8ToWord8#
+  , testPrimop "eqInt8#" Primop.eqInt8# Wrapper.eqInt8#
+  , testPrimop "geInt8#" Primop.geInt8# Wrapper.geInt8#
+  , testPrimop "gtInt8#" Primop.gtInt8# Wrapper.gtInt8#
+  , testPrimop "leInt8#" Primop.leInt8# Wrapper.leInt8#
+  , testPrimop "ltInt8#" Primop.ltInt8# Wrapper.ltInt8#
+  , testPrimop "neInt8#" Primop.neInt8# Wrapper.neInt8#
+  , testPrimop "word8ToWord#" Primop.word8ToWord# Wrapper.word8ToWord#
+  , testPrimop "wordToWord8#" Primop.wordToWord8# Wrapper.wordToWord8#
+  , testPrimop "plusWord8#" Primop.plusWord8# Wrapper.plusWord8#
+  , testPrimop "subWord8#" Primop.subWord8# Wrapper.subWord8#
+  , testPrimop "timesWord8#" Primop.timesWord8# Wrapper.timesWord8#
+  , testPrimop "quotWord8#" Primop.quotWord8# Wrapper.quotWord8#
+  , testPrimop "remWord8#" Primop.remWord8# Wrapper.remWord8#
+  , testPrimop "quotRemWord8#" Primop.quotRemWord8# Wrapper.quotRemWord8#
+  , testPrimop "andWord8#" Primop.andWord8# Wrapper.andWord8#
+  , testPrimop "orWord8#" Primop.orWord8# Wrapper.orWord8#
+  , testPrimop "xorWord8#" Primop.xorWord8# Wrapper.xorWord8#
+  , testPrimop "notWord8#" Primop.notWord8# Wrapper.notWord8#
+  , testPrimop "uncheckedShiftLWord8#" Primop.uncheckedShiftLWord8# Wrapper.uncheckedShiftLWord8#
+  , testPrimop "uncheckedShiftRLWord8#" Primop.uncheckedShiftRLWord8# Wrapper.uncheckedShiftRLWord8#
+  , testPrimop "word8ToInt8#" Primop.word8ToInt8# Wrapper.word8ToInt8#
+  , testPrimop "eqWord8#" Primop.eqWord8# Wrapper.eqWord8#
+  , testPrimop "geWord8#" Primop.geWord8# Wrapper.geWord8#
+  , testPrimop "gtWord8#" Primop.gtWord8# Wrapper.gtWord8#
+  , testPrimop "leWord8#" Primop.leWord8# Wrapper.leWord8#
+  , testPrimop "ltWord8#" Primop.ltWord8# Wrapper.ltWord8#
+  , testPrimop "neWord8#" Primop.neWord8# Wrapper.neWord8#
+  , testPrimop "int16ToInt#" Primop.int16ToInt# Wrapper.int16ToInt#
+  , testPrimop "intToInt16#" Primop.intToInt16# Wrapper.intToInt16#
+  , testPrimop "negateInt16#" Primop.negateInt16# Wrapper.negateInt16#
+  , testPrimop "plusInt16#" Primop.plusInt16# Wrapper.plusInt16#
+  , testPrimop "subInt16#" Primop.subInt16# Wrapper.subInt16#
+  , testPrimop "timesInt16#" Primop.timesInt16# Wrapper.timesInt16#
+  , testPrimop "quotInt16#" Primop.quotInt16# Wrapper.quotInt16#
+  , testPrimop "remInt16#" Primop.remInt16# Wrapper.remInt16#
+  , testPrimop "quotRemInt16#" Primop.quotRemInt16# Wrapper.quotRemInt16#
+  , testPrimop "uncheckedShiftLInt16#" Primop.uncheckedShiftLInt16# Wrapper.uncheckedShiftLInt16#
+  , testPrimop "uncheckedShiftRAInt16#" Primop.uncheckedShiftRAInt16# Wrapper.uncheckedShiftRAInt16#
+  , testPrimop "uncheckedShiftRLInt16#" Primop.uncheckedShiftRLInt16# Wrapper.uncheckedShiftRLInt16#
+  , testPrimop "int16ToWord16#" Primop.int16ToWord16# Wrapper.int16ToWord16#
+  , testPrimop "eqInt16#" Primop.eqInt16# Wrapper.eqInt16#
+  , testPrimop "geInt16#" Primop.geInt16# Wrapper.geInt16#
+  , testPrimop "gtInt16#" Primop.gtInt16# Wrapper.gtInt16#
+  , testPrimop "leInt16#" Primop.leInt16# Wrapper.leInt16#
+  , testPrimop "ltInt16#" Primop.ltInt16# Wrapper.ltInt16#
+  , testPrimop "neInt16#" Primop.neInt16# Wrapper.neInt16#
+  , testPrimop "word16ToWord#" Primop.word16ToWord# Wrapper.word16ToWord#
+  , testPrimop "wordToWord16#" Primop.wordToWord16# Wrapper.wordToWord16#
+  , testPrimop "plusWord16#" Primop.plusWord16# Wrapper.plusWord16#
+  , testPrimop "subWord16#" Primop.subWord16# Wrapper.subWord16#
+  , testPrimop "timesWord16#" Primop.timesWord16# Wrapper.timesWord16#
+  , testPrimop "quotWord16#" Primop.quotWord16# Wrapper.quotWord16#
+  , testPrimop "remWord16#" Primop.remWord16# Wrapper.remWord16#
+  , testPrimop "quotRemWord16#" Primop.quotRemWord16# Wrapper.quotRemWord16#
+  , testPrimop "andWord16#" Primop.andWord16# Wrapper.andWord16#
+  , testPrimop "orWord16#" Primop.orWord16# Wrapper.orWord16#
+  , testPrimop "xorWord16#" Primop.xorWord16# Wrapper.xorWord16#
+  , testPrimop "notWord16#" Primop.notWord16# Wrapper.notWord16#
+  , testPrimop "uncheckedShiftLWord16#" Primop.uncheckedShiftLWord16# Wrapper.uncheckedShiftLWord16#
+  , testPrimop "uncheckedShiftRLWord16#" Primop.uncheckedShiftRLWord16# Wrapper.uncheckedShiftRLWord16#
+  , testPrimop "word16ToInt16#" Primop.word16ToInt16# Wrapper.word16ToInt16#
+  , testPrimop "eqWord16#" Primop.eqWord16# Wrapper.eqWord16#
+  , testPrimop "geWord16#" Primop.geWord16# Wrapper.geWord16#
+  , testPrimop "gtWord16#" Primop.gtWord16# Wrapper.gtWord16#
+  , testPrimop "leWord16#" Primop.leWord16# Wrapper.leWord16#
+  , testPrimop "ltWord16#" Primop.ltWord16# Wrapper.ltWord16#
+  , testPrimop "neWord16#" Primop.neWord16# Wrapper.neWord16#
+  , testPrimop "int32ToInt#" Primop.int32ToInt# Wrapper.int32ToInt#
+  , testPrimop "intToInt32#" Primop.intToInt32# Wrapper.intToInt32#
+  , testPrimop "negateInt32#" Primop.negateInt32# Wrapper.negateInt32#
+  , testPrimop "plusInt32#" Primop.plusInt32# Wrapper.plusInt32#
+  , testPrimop "subInt32#" Primop.subInt32# Wrapper.subInt32#
+  , testPrimop "timesInt32#" Primop.timesInt32# Wrapper.timesInt32#
+  , testPrimop "quotInt32#" Primop.quotInt32# Wrapper.quotInt32#
+  , testPrimop "remInt32#" Primop.remInt32# Wrapper.remInt32#
+  , testPrimop "quotRemInt32#" Primop.quotRemInt32# Wrapper.quotRemInt32#
+  , testPrimop "uncheckedShiftLInt32#" Primop.uncheckedShiftLInt32# Wrapper.uncheckedShiftLInt32#
+  , testPrimop "uncheckedShiftRAInt32#" Primop.uncheckedShiftRAInt32# Wrapper.uncheckedShiftRAInt32#
+  , testPrimop "uncheckedShiftRLInt32#" Primop.uncheckedShiftRLInt32# Wrapper.uncheckedShiftRLInt32#
+  , testPrimop "int32ToWord32#" Primop.int32ToWord32# Wrapper.int32ToWord32#
+  , testPrimop "eqInt32#" Primop.eqInt32# Wrapper.eqInt32#
+  , testPrimop "geInt32#" Primop.geInt32# Wrapper.geInt32#
+  , testPrimop "gtInt32#" Primop.gtInt32# Wrapper.gtInt32#
+  , testPrimop "leInt32#" Primop.leInt32# Wrapper.leInt32#
+  , testPrimop "ltInt32#" Primop.ltInt32# Wrapper.ltInt32#
+  , testPrimop "neInt32#" Primop.neInt32# Wrapper.neInt32#
+  , testPrimop "word32ToWord#" Primop.word32ToWord# Wrapper.word32ToWord#
+  , testPrimop "wordToWord32#" Primop.wordToWord32# Wrapper.wordToWord32#
+  , testPrimop "plusWord32#" Primop.plusWord32# Wrapper.plusWord32#
+  , testPrimop "subWord32#" Primop.subWord32# Wrapper.subWord32#
+  , testPrimop "timesWord32#" Primop.timesWord32# Wrapper.timesWord32#
+  , testPrimop "quotWord32#" Primop.quotWord32# Wrapper.quotWord32#
+  , testPrimop "remWord32#" Primop.remWord32# Wrapper.remWord32#
+  , testPrimop "quotRemWord32#" Primop.quotRemWord32# Wrapper.quotRemWord32#
+  , testPrimop "andWord32#" Primop.andWord32# Wrapper.andWord32#
+  , testPrimop "orWord32#" Primop.orWord32# Wrapper.orWord32#
+  , testPrimop "xorWord32#" Primop.xorWord32# Wrapper.xorWord32#
+  , testPrimop "notWord32#" Primop.notWord32# Wrapper.notWord32#
+  , testPrimop "uncheckedShiftLWord32#" Primop.uncheckedShiftLWord32# Wrapper.uncheckedShiftLWord32#
+  , testPrimop "uncheckedShiftRLWord32#" Primop.uncheckedShiftRLWord32# Wrapper.uncheckedShiftRLWord32#
+  , testPrimop "word32ToInt32#" Primop.word32ToInt32# Wrapper.word32ToInt32#
+  , testPrimop "eqWord32#" Primop.eqWord32# Wrapper.eqWord32#
+  , testPrimop "geWord32#" Primop.geWord32# Wrapper.geWord32#
+  , testPrimop "gtWord32#" Primop.gtWord32# Wrapper.gtWord32#
+  , testPrimop "leWord32#" Primop.leWord32# Wrapper.leWord32#
+  , testPrimop "ltWord32#" Primop.ltWord32# Wrapper.ltWord32#
+  , testPrimop "neWord32#" Primop.neWord32# Wrapper.neWord32#
+  , testPrimop "int64ToInt#" Primop.int64ToInt# Wrapper.int64ToInt#
+  , testPrimop "intToInt64#" Primop.intToInt64# Wrapper.intToInt64#
+  , testPrimop "negateInt64#" Primop.negateInt64# Wrapper.negateInt64#
+  , testPrimop "plusInt64#" Primop.plusInt64# Wrapper.plusInt64#
+  , testPrimop "subInt64#" Primop.subInt64# Wrapper.subInt64#
+  , testPrimop "timesInt64#" Primop.timesInt64# Wrapper.timesInt64#
+  , testPrimop "quotInt64#" Primop.quotInt64# Wrapper.quotInt64#
+  , testPrimop "remInt64#" Primop.remInt64# Wrapper.remInt64#
+  , testPrimop "uncheckedIShiftL64#" Primop.uncheckedIShiftL64# Wrapper.uncheckedIShiftL64#
+  , testPrimop "uncheckedIShiftRA64#" Primop.uncheckedIShiftRA64# Wrapper.uncheckedIShiftRA64#
+  , testPrimop "uncheckedIShiftRL64#" Primop.uncheckedIShiftRL64# Wrapper.uncheckedIShiftRL64#
+  , testPrimop "int64ToWord64#" Primop.int64ToWord64# Wrapper.int64ToWord64#
+  , testPrimop "eqInt64#" Primop.eqInt64# Wrapper.eqInt64#
+  , testPrimop "geInt64#" Primop.geInt64# Wrapper.geInt64#
+  , testPrimop "gtInt64#" Primop.gtInt64# Wrapper.gtInt64#
+  , testPrimop "leInt64#" Primop.leInt64# Wrapper.leInt64#
+  , testPrimop "ltInt64#" Primop.ltInt64# Wrapper.ltInt64#
+  , testPrimop "neInt64#" Primop.neInt64# Wrapper.neInt64#
+  , testPrimop "word64ToWord#" Primop.word64ToWord# Wrapper.word64ToWord#
+  , testPrimop "wordToWord64#" Primop.wordToWord64# Wrapper.wordToWord64#
+  , testPrimop "plusWord64#" Primop.plusWord64# Wrapper.plusWord64#
+  , testPrimop "subWord64#" Primop.subWord64# Wrapper.subWord64#
+  , testPrimop "timesWord64#" Primop.timesWord64# Wrapper.timesWord64#
+  , testPrimop "quotWord64#" Primop.quotWord64# Wrapper.quotWord64#
+  , testPrimop "remWord64#" Primop.remWord64# Wrapper.remWord64#
+  , testPrimop "and64#" Primop.and64# Wrapper.and64#
+  , testPrimop "or64#" Primop.or64# Wrapper.or64#
+  , testPrimop "xor64#" Primop.xor64# Wrapper.xor64#
+  , testPrimop "not64#" Primop.not64# Wrapper.not64#
+  , testPrimop "uncheckedShiftL64#" Primop.uncheckedShiftL64# Wrapper.uncheckedShiftL64#
+  , testPrimop "uncheckedShiftRL64#" Primop.uncheckedShiftRL64# Wrapper.uncheckedShiftRL64#
+  , testPrimop "word64ToInt64#" Primop.word64ToInt64# Wrapper.word64ToInt64#
+  , testPrimop "eqWord64#" Primop.eqWord64# Wrapper.eqWord64#
+  , testPrimop "geWord64#" Primop.geWord64# Wrapper.geWord64#
+  , testPrimop "gtWord64#" Primop.gtWord64# Wrapper.gtWord64#
+  , testPrimop "leWord64#" Primop.leWord64# Wrapper.leWord64#
+  , testPrimop "ltWord64#" Primop.ltWord64# Wrapper.ltWord64#
+  , testPrimop "neWord64#" Primop.neWord64# Wrapper.neWord64#
+  , testPrimop "+#" (Primop.+#) (Wrapper.+#)
+  , testPrimop "-#" (Primop.-#) (Wrapper.-#)
+  , testPrimop "*#" (Primop.*#) (Wrapper.*#)
+  , testPrimop "timesInt2#" Primop.timesInt2# Wrapper.timesInt2#
+  , testPrimop "mulIntMayOflo#" Primop.mulIntMayOflo# Wrapper.mulIntMayOflo#
+  , testPrimop "quotInt#" Primop.quotInt# Wrapper.quotInt#
+  , testPrimop "remInt#" Primop.remInt# Wrapper.remInt#
+  , testPrimop "quotRemInt#" Primop.quotRemInt# Wrapper.quotRemInt#
+  , testPrimop "andI#" Primop.andI# Wrapper.andI#
+  , testPrimop "orI#" Primop.orI# Wrapper.orI#
+  , testPrimop "xorI#" Primop.xorI# Wrapper.xorI#
+  , testPrimop "notI#" Primop.notI# Wrapper.notI#
+  , testPrimop "negateInt#" Primop.negateInt# Wrapper.negateInt#
+  , testPrimop "addIntC#" Primop.addIntC# Wrapper.addIntC#
+  , testPrimop "subIntC#" Primop.subIntC# Wrapper.subIntC#
+  , testPrimop ">#" (Primop.>#) (Wrapper.>#)
+  , testPrimop ">=#" (Primop.>=#) (Wrapper.>=#)
+  , testPrimop "==#" (Primop.==#) (Wrapper.==#)
+  , testPrimop "/=#" (Primop./=#) (Wrapper./=#)
+  , testPrimop "<#" (Primop.<#) (Wrapper.<#)
+  , testPrimop "<=#" (Primop.<=#) (Wrapper.<=#)
+  , testPrimop "chr#" Primop.chr# Wrapper.chr#
+  , testPrimop "int2Word#" Primop.int2Word# Wrapper.int2Word#
+  , testPrimop "uncheckedIShiftL#" Primop.uncheckedIShiftL# Wrapper.uncheckedIShiftL#
+  , testPrimop "uncheckedIShiftRA#" Primop.uncheckedIShiftRA# Wrapper.uncheckedIShiftRA#
+  , testPrimop "uncheckedIShiftRL#" Primop.uncheckedIShiftRL# Wrapper.uncheckedIShiftRL#
+  , testPrimop "plusWord#" Primop.plusWord# Wrapper.plusWord#
+  , testPrimop "addWordC#" Primop.addWordC# Wrapper.addWordC#
+  , testPrimop "subWordC#" Primop.subWordC# Wrapper.subWordC#
+  , testPrimop "plusWord2#" Primop.plusWord2# Wrapper.plusWord2#
+  , testPrimop "minusWord#" Primop.minusWord# Wrapper.minusWord#
+  , testPrimop "timesWord#" Primop.timesWord# Wrapper.timesWord#
+  , testPrimop "timesWord2#" Primop.timesWord2# Wrapper.timesWord2#
+  , testPrimop "quotWord#" Primop.quotWord# Wrapper.quotWord#
+  , testPrimop "remWord#" Primop.remWord# Wrapper.remWord#
+  , testPrimop "quotRemWord#" Primop.quotRemWord# Wrapper.quotRemWord#
+--  , testPrimop "quotRemWord2#" Primop.quotRemWord2# Wrapper.quotRemWord2#
+  , testPrimop "and#" Primop.and# Wrapper.and#
+  , testPrimop "or#" Primop.or# Wrapper.or#
+  , testPrimop "xor#" Primop.xor# Wrapper.xor#
+  , testPrimop "not#" Primop.not# Wrapper.not#
+  , testPrimop "uncheckedShiftL#" Primop.uncheckedShiftL# Wrapper.uncheckedShiftL#
+  , testPrimop "uncheckedShiftRL#" Primop.uncheckedShiftRL# Wrapper.uncheckedShiftRL#
+  , testPrimop "word2Int#" Primop.word2Int# Wrapper.word2Int#
+  , testPrimop "gtWord#" Primop.gtWord# Wrapper.gtWord#
+  , testPrimop "geWord#" Primop.geWord# Wrapper.geWord#
+  , testPrimop "eqWord#" Primop.eqWord# Wrapper.eqWord#
+  , testPrimop "neWord#" Primop.neWord# Wrapper.neWord#
+  , testPrimop "ltWord#" Primop.ltWord# Wrapper.ltWord#
+  , testPrimop "leWord#" Primop.leWord# Wrapper.leWord#
+  , testPrimop "popCnt8#" Primop.popCnt8# Wrapper.popCnt8#
+  , testPrimop "popCnt16#" Primop.popCnt16# Wrapper.popCnt16#
+  , testPrimop "popCnt32#" Primop.popCnt32# Wrapper.popCnt32#
+  , testPrimop "popCnt64#" Primop.popCnt64# Wrapper.popCnt64#
+  , testPrimop "popCnt#" Primop.popCnt# Wrapper.popCnt#
+  , testPrimop "pdep8#" Primop.pdep8# Wrapper.pdep8#
+  , testPrimop "pdep16#" Primop.pdep16# Wrapper.pdep16#
+  , testPrimop "pdep32#" Primop.pdep32# Wrapper.pdep32#
+  , testPrimop "pdep64#" Primop.pdep64# Wrapper.pdep64#
+  , testPrimop "pdep#" Primop.pdep# Wrapper.pdep#
+  , testPrimop "pext8#" Primop.pext8# Wrapper.pext8#
+  , testPrimop "pext16#" Primop.pext16# Wrapper.pext16#
+  , testPrimop "pext32#" Primop.pext32# Wrapper.pext32#
+  , testPrimop "pext64#" Primop.pext64# Wrapper.pext64#
+  , testPrimop "pext#" Primop.pext# Wrapper.pext#
+  , testPrimop "clz8#" Primop.clz8# Wrapper.clz8#
+  , testPrimop "clz16#" Primop.clz16# Wrapper.clz16#
+  , testPrimop "clz32#" Primop.clz32# Wrapper.clz32#
+  , testPrimop "clz64#" Primop.clz64# Wrapper.clz64#
+  , testPrimop "clz#" Primop.clz# Wrapper.clz#
+  , testPrimop "ctz8#" Primop.ctz8# Wrapper.ctz8#
+  , testPrimop "ctz16#" Primop.ctz16# Wrapper.ctz16#
+  , testPrimop "ctz32#" Primop.ctz32# Wrapper.ctz32#
+  , testPrimop "ctz64#" Primop.ctz64# Wrapper.ctz64#
+  , testPrimop "ctz#" Primop.ctz# Wrapper.ctz#
+  , testPrimop "byteSwap16#" Primop.byteSwap16# Wrapper.byteSwap16#
+  , testPrimop "byteSwap32#" Primop.byteSwap32# Wrapper.byteSwap32#
+  , testPrimop "byteSwap64#" Primop.byteSwap64# Wrapper.byteSwap64#
+  , testPrimop "byteSwap#" Primop.byteSwap# Wrapper.byteSwap#
+  , testPrimop "bitReverse8#" Primop.bitReverse8# Wrapper.bitReverse8#
+  , testPrimop "bitReverse16#" Primop.bitReverse16# Wrapper.bitReverse16#
+  , testPrimop "bitReverse32#" Primop.bitReverse32# Wrapper.bitReverse32#
+  , testPrimop "bitReverse64#" Primop.bitReverse64# Wrapper.bitReverse64#
+  , testPrimop "bitReverse#" Primop.bitReverse# Wrapper.bitReverse#
+  , testPrimop "narrow8Int#" Primop.narrow8Int# Wrapper.narrow8Int#
+  , testPrimop "narrow16Int#" Primop.narrow16Int# Wrapper.narrow16Int#
+  , testPrimop "narrow32Int#" Primop.narrow32Int# Wrapper.narrow32Int#
+  , testPrimop "narrow8Word#" Primop.narrow8Word# Wrapper.narrow8Word#
+  , testPrimop "narrow16Word#" Primop.narrow16Word# Wrapper.narrow16Word#
+  , testPrimop "narrow32Word#" Primop.narrow32Word# Wrapper.narrow32Word#
+  ]
+
+instance TestPrimop (Char# -> Char# -> Int#) where
+  testPrimop s l r = Property s $ \ (uChar#-> x0) (uChar#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Char# -> Int#) where
+  testPrimop s l r = Property s $ \ (uChar#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Int# -> Int# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Int# -> Int# -> (# Int#,Int# #)) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> WTUP2(wInt#,wInt#, (l x0 x1)) === WTUP2(wInt#,wInt#, (r x0 x1))
+
+instance TestPrimop (Int# -> Int# -> (# Int#,Int#,Int# #)) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) (uInt#-> x1) -> WTUP3(wInt#,wInt#,wInt#, (l x0 x1)) === WTUP3(wInt#,wInt#,wInt#, (r x0 x1))
+
+instance TestPrimop (Int# -> Char#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wChar# (l x0) === wChar# (r x0)
+
+instance TestPrimop (Int# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Int# -> Int16#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wInt16# (l x0) === wInt16# (r x0)
+
+instance TestPrimop (Int# -> Int32#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wInt32# (l x0) === wInt32# (r x0)
+
+instance TestPrimop (Int# -> Int64#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wInt64# (l x0) === wInt64# (r x0)
+
+instance TestPrimop (Int# -> Int8#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wInt8# (l x0) === wInt8# (r x0)
+
+instance TestPrimop (Int# -> Word#) where
+  testPrimop s l r = Property s $ \ (uInt#-> x0) -> wWord# (l x0) === wWord# (r x0)
+
+instance TestPrimop (Int16# -> Int# -> Int16#) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt#-> x1) -> wInt16# (l x0 x1) === wInt16# (r x0 x1)
+
+instance TestPrimop (Int16# -> Int16# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt16#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Int16# -> Int16# -> Int16#) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt16#-> x1) -> wInt16# (l x0 x1) === wInt16# (r x0 x1)
+
+instance TestPrimop (Int16# -> Int16# -> (# Int16#,Int16# #)) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) (uInt16#-> x1) -> WTUP2(wInt16#,wInt16#, (l x0 x1)) === WTUP2(wInt16#,wInt16#, (r x0 x1))
+
+instance TestPrimop (Int16# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Int16# -> Int16#) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) -> wInt16# (l x0) === wInt16# (r x0)
+
+instance TestPrimop (Int16# -> Word16#) where
+  testPrimop s l r = Property s $ \ (uInt16#-> x0) -> wWord16# (l x0) === wWord16# (r x0)
+
+instance TestPrimop (Int32# -> Int# -> Int32#) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt#-> x1) -> wInt32# (l x0 x1) === wInt32# (r x0 x1)
+
+instance TestPrimop (Int32# -> Int32# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt32#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Int32# -> Int32# -> Int32#) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt32#-> x1) -> wInt32# (l x0 x1) === wInt32# (r x0 x1)
+
+instance TestPrimop (Int32# -> Int32# -> (# Int32#,Int32# #)) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) (uInt32#-> x1) -> WTUP2(wInt32#,wInt32#, (l x0 x1)) === WTUP2(wInt32#,wInt32#, (r x0 x1))
+
+instance TestPrimop (Int32# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Int32# -> Int32#) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) -> wInt32# (l x0) === wInt32# (r x0)
+
+instance TestPrimop (Int32# -> Word32#) where
+  testPrimop s l r = Property s $ \ (uInt32#-> x0) -> wWord32# (l x0) === wWord32# (r x0)
+
+instance TestPrimop (Int64# -> Int# -> Int64#) where
+  testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt#-> x1) -> wInt64# (l x0 x1) === wInt64# (r x0 x1)
+
+instance TestPrimop (Int64# -> Int64# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt64#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Int64# -> Int64# -> Int64#) where
+  testPrimop s l r = Property s $ \ (uInt64#-> x0) (uInt64#-> x1) -> wInt64# (l x0 x1) === wInt64# (r x0 x1)
+
+instance TestPrimop (Int64# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt64#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Int64# -> Int64#) where
+  testPrimop s l r = Property s $ \ (uInt64#-> x0) -> wInt64# (l x0) === wInt64# (r x0)
+
+instance TestPrimop (Int64# -> Word64#) where
+  testPrimop s l r = Property s $ \ (uInt64#-> x0) -> wWord64# (l x0) === wWord64# (r x0)
+
+instance TestPrimop (Int8# -> Int# -> Int8#) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt#-> x1) -> wInt8# (l x0 x1) === wInt8# (r x0 x1)
+
+instance TestPrimop (Int8# -> Int8# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt8#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Int8# -> Int8# -> Int8#) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt8#-> x1) -> wInt8# (l x0 x1) === wInt8# (r x0 x1)
+
+instance TestPrimop (Int8# -> Int8# -> (# Int8#,Int8# #)) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) (uInt8#-> x1) -> WTUP2(wInt8#,wInt8#, (l x0 x1)) === WTUP2(wInt8#,wInt8#, (r x0 x1))
+
+instance TestPrimop (Int8# -> Int#) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Int8# -> Int8#) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) -> wInt8# (l x0) === wInt8# (r x0)
+
+instance TestPrimop (Int8# -> Word8#) where
+  testPrimop s l r = Property s $ \ (uInt8#-> x0) -> wWord8# (l x0) === wWord8# (r x0)
+
+instance TestPrimop (Word# -> Int# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) (uInt#-> x1) -> wWord# (l x0 x1) === wWord# (r x0 x1)
+
+instance TestPrimop (Word# -> Word# -> Word# -> (# Word#,Word# #)) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) (uWord#-> x2) -> WTUP2(wWord#,wWord#, (l x0 x1 x2)) === WTUP2(wWord#,wWord#, (r x0 x1 x2))
+
+instance TestPrimop (Word# -> Word# -> Int#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Word# -> Word# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) -> wWord# (l x0 x1) === wWord# (r x0 x1)
+
+instance TestPrimop (Word# -> Word# -> (# Word#,Int# #)) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) -> WTUP2(wWord#,wInt#, (l x0 x1)) === WTUP2(wWord#,wInt#, (r x0 x1))
+
+instance TestPrimop (Word# -> Word# -> (# Word#,Word# #)) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) (uWord#-> x1) -> WTUP2(wWord#,wWord#, (l x0 x1)) === WTUP2(wWord#,wWord#, (r x0 x1))
+
+instance TestPrimop (Word# -> Int#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) -> wInt# (l x0) === wInt# (r x0)
+
+instance TestPrimop (Word# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) -> wWord# (l x0) === wWord# (r x0)
+
+instance TestPrimop (Word# -> Word16#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) -> wWord16# (l x0) === wWord16# (r x0)
+
+instance TestPrimop (Word# -> Word32#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) -> wWord32# (l x0) === wWord32# (r x0)
+
+instance TestPrimop (Word# -> Word64#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) -> wWord64# (l x0) === wWord64# (r x0)
+
+instance TestPrimop (Word# -> Word8#) where
+  testPrimop s l r = Property s $ \ (uWord#-> x0) -> wWord8# (l x0) === wWord8# (r x0)
+
+instance TestPrimop (Word16# -> Int# -> Word16#) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) (uInt#-> x1) -> wWord16# (l x0 x1) === wWord16# (r x0 x1)
+
+instance TestPrimop (Word16# -> Word16# -> Int#) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) (uWord16#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Word16# -> Word16# -> Word16#) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) (uWord16#-> x1) -> wWord16# (l x0 x1) === wWord16# (r x0 x1)
+
+instance TestPrimop (Word16# -> Word16# -> (# Word16#,Word16# #)) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) (uWord16#-> x1) -> WTUP2(wWord16#,wWord16#, (l x0 x1)) === WTUP2(wWord16#,wWord16#, (r x0 x1))
+
+instance TestPrimop (Word16# -> Int16#) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) -> wInt16# (l x0) === wInt16# (r x0)
+
+instance TestPrimop (Word16# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) -> wWord# (l x0) === wWord# (r x0)
+
+instance TestPrimop (Word16# -> Word16#) where
+  testPrimop s l r = Property s $ \ (uWord16#-> x0) -> wWord16# (l x0) === wWord16# (r x0)
+
+instance TestPrimop (Word32# -> Int# -> Word32#) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) (uInt#-> x1) -> wWord32# (l x0 x1) === wWord32# (r x0 x1)
+
+instance TestPrimop (Word32# -> Word32# -> Int#) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) (uWord32#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Word32# -> Word32# -> Word32#) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) (uWord32#-> x1) -> wWord32# (l x0 x1) === wWord32# (r x0 x1)
+
+instance TestPrimop (Word32# -> Word32# -> (# Word32#,Word32# #)) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) (uWord32#-> x1) -> WTUP2(wWord32#,wWord32#, (l x0 x1)) === WTUP2(wWord32#,wWord32#, (r x0 x1))
+
+instance TestPrimop (Word32# -> Int32#) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) -> wInt32# (l x0) === wInt32# (r x0)
+
+instance TestPrimop (Word32# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) -> wWord# (l x0) === wWord# (r x0)
+
+instance TestPrimop (Word32# -> Word32#) where
+  testPrimop s l r = Property s $ \ (uWord32#-> x0) -> wWord32# (l x0) === wWord32# (r x0)
+
+instance TestPrimop (Word64# -> Int# -> Word64#) where
+  testPrimop s l r = Property s $ \ (uWord64#-> x0) (uInt#-> x1) -> wWord64# (l x0 x1) === wWord64# (r x0 x1)
+
+instance TestPrimop (Word64# -> Word64# -> Int#) where
+  testPrimop s l r = Property s $ \ (uWord64#-> x0) (uWord64#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Word64# -> Word64# -> Word64#) where
+  testPrimop s l r = Property s $ \ (uWord64#-> x0) (uWord64#-> x1) -> wWord64# (l x0 x1) === wWord64# (r x0 x1)
+
+instance TestPrimop (Word64# -> Int64#) where
+  testPrimop s l r = Property s $ \ (uWord64#-> x0) -> wInt64# (l x0) === wInt64# (r x0)
+
+instance TestPrimop (Word64# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord64#-> x0) -> wWord# (l x0) === wWord# (r x0)
+
+instance TestPrimop (Word64# -> Word64#) where
+  testPrimop s l r = Property s $ \ (uWord64#-> x0) -> wWord64# (l x0) === wWord64# (r x0)
+
+instance TestPrimop (Word8# -> Int# -> Word8#) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) (uInt#-> x1) -> wWord8# (l x0 x1) === wWord8# (r x0 x1)
+
+instance TestPrimop (Word8# -> Word8# -> Int#) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) (uWord8#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
+
+instance TestPrimop (Word8# -> Word8# -> Word8#) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) (uWord8#-> x1) -> wWord8# (l x0 x1) === wWord8# (r x0 x1)
+
+instance TestPrimop (Word8# -> Word8# -> (# Word8#,Word8# #)) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) (uWord8#-> x1) -> WTUP2(wWord8#,wWord8#, (l x0 x1)) === WTUP2(wWord8#,wWord8#, (r x0 x1))
+
+instance TestPrimop (Word8# -> Int8#) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) -> wInt8# (l x0) === wInt8# (r x0)
 
+instance TestPrimop (Word8# -> Word#) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) -> wWord# (l x0) === wWord# (r x0)
 
-main = runTests testNumberRefs
+instance TestPrimop (Word8# -> Word8#) where
+  testPrimop s l r = Property s $ \ (uWord8#-> x0) -> wWord8# (l x0) === wWord8# (r x0)


=====================================
testsuite/tests/numeric/should_run/foundation.stdout
=====================================
@@ -1,540 +1,1050 @@
 Group ALL
-  Group Int
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Int8
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Int16
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Int32
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Int64
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Integer
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Word
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Word8
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Word16
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Word32
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
-  Group Word64
-    Group Integral
-      Running FromIntegral(Integer(a)) == a
-        Passed 100 iterations
-    Group Property
-      Running Eq
-        Passed 100 iterations
-      Running Show
-        Passed 100 iterations
-      Running Ord
-        Passed 100 iterations
-      Running <
-        Passed 100 iterations
-    Group Additive
-      Running a + azero == a
-        Passed 100 iterations
-      Running azero + a == a
-        Passed 100 iterations
-      Running a + b == b + a
-        Passed 100 iterations
-    Group Multiplicative
-      Running a * 1 == a
-        Passed 100 iterations
-      Running 1 * a == a
-        Passed 100 iterations
-      Running multiplication commutative
-        Passed 100 iterations
-      Running a * b == Integer(a) * Integer(b)
-        Passed 100 iterations
-    Group Divisible
-      Running (x `div` y) * y + (x `mod` y) == x
-        Passed 100 iterations
-    Group Precedence
-      Running + and - (1)
-        Passed 100 iterations
-      Running + and - (2)
-        Passed 100 iterations
-      Running + and * (1)
-        Passed 100 iterations
-      Running + and * (2)
-        Passed 100 iterations
-      Running - and * (1)
-        Passed 100 iterations
-      Running - and * (2)
-        Passed 100 iterations
-      Running * and ^ (1)
-        Passed 100 iterations
-      Running * and ^ (2)
-        Passed 100 iterations
+  Group ALL
+    Group Int
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Int8
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Int16
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Int32
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Int64
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Integer
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Word
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Word8
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Word16
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Word32
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+    Group Word64
+      Group Integral
+        Running FromIntegral(Integer(a)) == a
+          Passed 100 iterations
+      Group Property
+        Running Eq
+          Passed 100 iterations
+        Running Show
+          Passed 100 iterations
+        Running Ord
+          Passed 100 iterations
+        Running <
+          Passed 100 iterations
+      Group Additive
+        Running a + azero == a
+          Passed 100 iterations
+        Running azero + a == a
+          Passed 100 iterations
+        Running a + b == b + a
+          Passed 100 iterations
+      Group Multiplicative
+        Running a * 1 == a
+          Passed 100 iterations
+        Running 1 * a == a
+          Passed 100 iterations
+        Running multiplication commutative
+          Passed 100 iterations
+        Running a * b == Integer(a) * Integer(b)
+          Passed 100 iterations
+      Group Divisible
+        Running (x `div` y) * y + (x `mod` y) == x
+          Passed 100 iterations
+      Group Precedence
+        Running + and - (1)
+          Passed 100 iterations
+        Running + and - (2)
+          Passed 100 iterations
+        Running + and * (1)
+          Passed 100 iterations
+        Running + and * (2)
+          Passed 100 iterations
+        Running - and * (1)
+          Passed 100 iterations
+        Running - and * (2)
+          Passed 100 iterations
+        Running * and ^ (1)
+          Passed 100 iterations
+        Running * and ^ (2)
+          Passed 100 iterations
+  Group primop
+    Running gtChar#
+      Passed 100 iterations
+    Running geChar#
+      Passed 100 iterations
+    Running eqChar#
+      Passed 100 iterations
+    Running neChar#
+      Passed 100 iterations
+    Running ltChar#
+      Passed 100 iterations
+    Running leChar#
+      Passed 100 iterations
+    Running ord#
+      Passed 100 iterations
+    Running int8ToInt#
+      Passed 100 iterations
+    Running intToInt8#
+      Passed 100 iterations
+    Running negateInt8#
+      Passed 100 iterations
+    Running plusInt8#
+      Passed 100 iterations
+    Running subInt8#
+      Passed 100 iterations
+    Running timesInt8#
+      Passed 100 iterations
+    Running quotInt8#
+      Passed 100 iterations
+    Running remInt8#
+      Passed 100 iterations
+    Running quotRemInt8#
+      Passed 100 iterations
+    Running uncheckedShiftLInt8#
+      Passed 100 iterations
+    Running uncheckedShiftRAInt8#
+      Passed 100 iterations
+    Running uncheckedShiftRLInt8#
+      Passed 100 iterations
+    Running int8ToWord8#
+      Passed 100 iterations
+    Running eqInt8#
+      Passed 100 iterations
+    Running geInt8#
+      Passed 100 iterations
+    Running gtInt8#
+      Passed 100 iterations
+    Running leInt8#
+      Passed 100 iterations
+    Running ltInt8#
+      Passed 100 iterations
+    Running neInt8#
+      Passed 100 iterations
+    Running word8ToWord#
+      Passed 100 iterations
+    Running wordToWord8#
+      Passed 100 iterations
+    Running plusWord8#
+      Passed 100 iterations
+    Running subWord8#
+      Passed 100 iterations
+    Running timesWord8#
+      Passed 100 iterations
+    Running quotWord8#
+      Passed 100 iterations
+    Running remWord8#
+      Passed 100 iterations
+    Running quotRemWord8#
+      Passed 100 iterations
+    Running andWord8#
+      Passed 100 iterations
+    Running orWord8#
+      Passed 100 iterations
+    Running xorWord8#
+      Passed 100 iterations
+    Running notWord8#
+      Passed 100 iterations
+    Running uncheckedShiftLWord8#
+      Passed 100 iterations
+    Running uncheckedShiftRLWord8#
+      Passed 100 iterations
+    Running word8ToInt8#
+      Passed 100 iterations
+    Running eqWord8#
+      Passed 100 iterations
+    Running geWord8#
+      Passed 100 iterations
+    Running gtWord8#
+      Passed 100 iterations
+    Running leWord8#
+      Passed 100 iterations
+    Running ltWord8#
+      Passed 100 iterations
+    Running neWord8#
+      Passed 100 iterations
+    Running int16ToInt#
+      Passed 100 iterations
+    Running intToInt16#
+      Passed 100 iterations
+    Running negateInt16#
+      Passed 100 iterations
+    Running plusInt16#
+      Passed 100 iterations
+    Running subInt16#
+      Passed 100 iterations
+    Running timesInt16#
+      Passed 100 iterations
+    Running quotInt16#
+      Passed 100 iterations
+    Running remInt16#
+      Passed 100 iterations
+    Running quotRemInt16#
+      Passed 100 iterations
+    Running uncheckedShiftLInt16#
+      Passed 100 iterations
+    Running uncheckedShiftRAInt16#
+      Passed 100 iterations
+    Running uncheckedShiftRLInt16#
+      Passed 100 iterations
+    Running int16ToWord16#
+      Passed 100 iterations
+    Running eqInt16#
+      Passed 100 iterations
+    Running geInt16#
+      Passed 100 iterations
+    Running gtInt16#
+      Passed 100 iterations
+    Running leInt16#
+      Passed 100 iterations
+    Running ltInt16#
+      Passed 100 iterations
+    Running neInt16#
+      Passed 100 iterations
+    Running word16ToWord#
+      Passed 100 iterations
+    Running wordToWord16#
+      Passed 100 iterations
+    Running plusWord16#
+      Passed 100 iterations
+    Running subWord16#
+      Passed 100 iterations
+    Running timesWord16#
+      Passed 100 iterations
+    Running quotWord16#
+      Passed 100 iterations
+    Running remWord16#
+      Passed 100 iterations
+    Running quotRemWord16#
+      Passed 100 iterations
+    Running andWord16#
+      Passed 100 iterations
+    Running orWord16#
+      Passed 100 iterations
+    Running xorWord16#
+      Passed 100 iterations
+    Running notWord16#
+      Passed 100 iterations
+    Running uncheckedShiftLWord16#
+      Passed 100 iterations
+    Running uncheckedShiftRLWord16#
+      Passed 100 iterations
+    Running word16ToInt16#
+      Passed 100 iterations
+    Running eqWord16#
+      Passed 100 iterations
+    Running geWord16#
+      Passed 100 iterations
+    Running gtWord16#
+      Passed 100 iterations
+    Running leWord16#
+      Passed 100 iterations
+    Running ltWord16#
+      Passed 100 iterations
+    Running neWord16#
+      Passed 100 iterations
+    Running int32ToInt#
+      Passed 100 iterations
+    Running intToInt32#
+      Passed 100 iterations
+    Running negateInt32#
+      Passed 100 iterations
+    Running plusInt32#
+      Passed 100 iterations
+    Running subInt32#
+      Passed 100 iterations
+    Running timesInt32#
+      Passed 100 iterations
+    Running quotInt32#
+      Passed 100 iterations
+    Running remInt32#
+      Passed 100 iterations
+    Running quotRemInt32#
+      Passed 100 iterations
+    Running uncheckedShiftLInt32#
+      Passed 100 iterations
+    Running uncheckedShiftRAInt32#
+      Passed 100 iterations
+    Running uncheckedShiftRLInt32#
+      Passed 100 iterations
+    Running int32ToWord32#
+      Passed 100 iterations
+    Running eqInt32#
+      Passed 100 iterations
+    Running geInt32#
+      Passed 100 iterations
+    Running gtInt32#
+      Passed 100 iterations
+    Running leInt32#
+      Passed 100 iterations
+    Running ltInt32#
+      Passed 100 iterations
+    Running neInt32#
+      Passed 100 iterations
+    Running word32ToWord#
+      Passed 100 iterations
+    Running wordToWord32#
+      Passed 100 iterations
+    Running plusWord32#
+      Passed 100 iterations
+    Running subWord32#
+      Passed 100 iterations
+    Running timesWord32#
+      Passed 100 iterations
+    Running quotWord32#
+      Passed 100 iterations
+    Running remWord32#
+      Passed 100 iterations
+    Running quotRemWord32#
+      Passed 100 iterations
+    Running andWord32#
+      Passed 100 iterations
+    Running orWord32#
+      Passed 100 iterations
+    Running xorWord32#
+      Passed 100 iterations
+    Running notWord32#
+      Passed 100 iterations
+    Running uncheckedShiftLWord32#
+      Passed 100 iterations
+    Running uncheckedShiftRLWord32#
+      Passed 100 iterations
+    Running word32ToInt32#
+      Passed 100 iterations
+    Running eqWord32#
+      Passed 100 iterations
+    Running geWord32#
+      Passed 100 iterations
+    Running gtWord32#
+      Passed 100 iterations
+    Running leWord32#
+      Passed 100 iterations
+    Running ltWord32#
+      Passed 100 iterations
+    Running neWord32#
+      Passed 100 iterations
+    Running int64ToInt#
+      Passed 100 iterations
+    Running intToInt64#
+      Passed 100 iterations
+    Running negateInt64#
+      Passed 100 iterations
+    Running plusInt64#
+      Passed 100 iterations
+    Running subInt64#
+      Passed 100 iterations
+    Running timesInt64#
+      Passed 100 iterations
+    Running quotInt64#
+      Passed 100 iterations
+    Running remInt64#
+      Passed 100 iterations
+    Running uncheckedIShiftL64#
+      Passed 100 iterations
+    Running uncheckedIShiftRA64#
+      Passed 100 iterations
+    Running uncheckedIShiftRL64#
+      Passed 100 iterations
+    Running int64ToWord64#
+      Passed 100 iterations
+    Running eqInt64#
+      Passed 100 iterations
+    Running geInt64#
+      Passed 100 iterations
+    Running gtInt64#
+      Passed 100 iterations
+    Running leInt64#
+      Passed 100 iterations
+    Running ltInt64#
+      Passed 100 iterations
+    Running neInt64#
+      Passed 100 iterations
+    Running word64ToWord#
+      Passed 100 iterations
+    Running wordToWord64#
+      Passed 100 iterations
+    Running plusWord64#
+      Passed 100 iterations
+    Running subWord64#
+      Passed 100 iterations
+    Running timesWord64#
+      Passed 100 iterations
+    Running quotWord64#
+      Passed 100 iterations
+    Running remWord64#
+      Passed 100 iterations
+    Running and64#
+      Passed 100 iterations
+    Running or64#
+      Passed 100 iterations
+    Running xor64#
+      Passed 100 iterations
+    Running not64#
+      Passed 100 iterations
+    Running uncheckedShiftL64#
+      Passed 100 iterations
+    Running uncheckedShiftRL64#
+      Passed 100 iterations
+    Running word64ToInt64#
+      Passed 100 iterations
+    Running eqWord64#
+      Passed 100 iterations
+    Running geWord64#
+      Passed 100 iterations
+    Running gtWord64#
+      Passed 100 iterations
+    Running leWord64#
+      Passed 100 iterations
+    Running ltWord64#
+      Passed 100 iterations
+    Running neWord64#
+      Passed 100 iterations
+    Running +#
+      Passed 100 iterations
+    Running -#
+      Passed 100 iterations
+    Running *#
+      Passed 100 iterations
+    Running timesInt2#
+      Passed 100 iterations
+    Running mulIntMayOflo#
+      Passed 100 iterations
+    Running quotInt#
+      Passed 100 iterations
+    Running remInt#
+      Passed 100 iterations
+    Running quotRemInt#
+      Passed 100 iterations
+    Running andI#
+      Passed 100 iterations
+    Running orI#
+      Passed 100 iterations
+    Running xorI#
+      Passed 100 iterations
+    Running notI#
+      Passed 100 iterations
+    Running negateInt#
+      Passed 100 iterations
+    Running addIntC#
+      Passed 100 iterations
+    Running subIntC#
+      Passed 100 iterations
+    Running >#
+      Passed 100 iterations
+    Running >=#
+      Passed 100 iterations
+    Running ==#
+      Passed 100 iterations
+    Running /=#
+      Passed 100 iterations
+    Running <#
+      Passed 100 iterations
+    Running <=#
+      Passed 100 iterations
+    Running chr#
+      Passed 100 iterations
+    Running int2Word#
+      Passed 100 iterations
+    Running uncheckedIShiftL#
+      Passed 100 iterations
+    Running uncheckedIShiftRA#
+      Passed 100 iterations
+    Running uncheckedIShiftRL#
+      Passed 100 iterations
+    Running plusWord#
+      Passed 100 iterations
+    Running addWordC#
+      Passed 100 iterations
+    Running subWordC#
+      Passed 100 iterations
+    Running plusWord2#
+      Passed 100 iterations
+    Running minusWord#
+      Passed 100 iterations
+    Running timesWord#
+      Passed 100 iterations
+    Running timesWord2#
+      Passed 100 iterations
+    Running quotWord#
+      Passed 100 iterations
+    Running remWord#
+      Passed 100 iterations
+    Running quotRemWord#
+      Passed 100 iterations
+    Running and#
+      Passed 100 iterations
+    Running or#
+      Passed 100 iterations
+    Running xor#
+      Passed 100 iterations
+    Running not#
+      Passed 100 iterations
+    Running uncheckedShiftL#
+      Passed 100 iterations
+    Running uncheckedShiftRL#
+      Passed 100 iterations
+    Running word2Int#
+      Passed 100 iterations
+    Running gtWord#
+      Passed 100 iterations
+    Running geWord#
+      Passed 100 iterations
+    Running eqWord#
+      Passed 100 iterations
+    Running neWord#
+      Passed 100 iterations
+    Running ltWord#
+      Passed 100 iterations
+    Running leWord#
+      Passed 100 iterations
+    Running popCnt8#
+      Passed 100 iterations
+    Running popCnt16#
+      Passed 100 iterations
+    Running popCnt32#
+      Passed 100 iterations
+    Running popCnt64#
+      Passed 100 iterations
+    Running popCnt#
+      Passed 100 iterations
+    Running pdep8#
+      Passed 100 iterations
+    Running pdep16#
+      Passed 100 iterations
+    Running pdep32#
+      Passed 100 iterations
+    Running pdep64#
+      Passed 100 iterations
+    Running pdep#
+      Passed 100 iterations
+    Running pext8#
+      Passed 100 iterations
+    Running pext16#
+      Passed 100 iterations
+    Running pext32#
+      Passed 100 iterations
+    Running pext64#
+      Passed 100 iterations
+    Running pext#
+      Passed 100 iterations
+    Running clz8#
+      Passed 100 iterations
+    Running clz16#
+      Passed 100 iterations
+    Running clz32#
+      Passed 100 iterations
+    Running clz64#
+      Passed 100 iterations
+    Running clz#
+      Passed 100 iterations
+    Running ctz8#
+      Passed 100 iterations
+    Running ctz16#
+      Passed 100 iterations
+    Running ctz32#
+      Passed 100 iterations
+    Running ctz64#
+      Passed 100 iterations
+    Running ctz#
+      Passed 100 iterations
+    Running byteSwap16#
+      Passed 100 iterations
+    Running byteSwap32#
+      Passed 100 iterations
+    Running byteSwap64#
+      Passed 100 iterations
+    Running byteSwap#
+      Passed 100 iterations
+    Running bitReverse8#
+      Passed 100 iterations
+    Running bitReverse16#
+      Passed 100 iterations
+    Running bitReverse32#
+      Passed 100 iterations
+    Running bitReverse64#
+      Passed 100 iterations
+    Running bitReverse#
+      Passed 100 iterations
+    Running narrow8Int#
+      Passed 100 iterations
+    Running narrow16Int#
+      Passed 100 iterations
+    Running narrow32Int#
+      Passed 100 iterations
+    Running narrow8Word#
+      Passed 100 iterations
+    Running narrow16Word#
+      Passed 100 iterations
+    Running narrow32Word#
+      Passed 100 iterations


=====================================
utils/genprimopcode/Main.hs
=====================================
@@ -10,11 +10,12 @@ import Parser
 import Syntax
 
 import Data.Char
-import Data.List (union, intersperse, intercalate, nub)
-import Data.Maybe ( catMaybes )
+import Data.List (union, intersperse, intercalate, nub, sort)
+import Data.Maybe ( catMaybes, mapMaybe )
 import System.Environment ( getArgs )
 import System.IO ( hSetEncoding, stdin, stdout, utf8 )
 
+
 vecOptions :: Entry -> [(String,String,Int)]
 vecOptions i =
     concat [vecs | OptionVector vecs <- opts i]
@@ -204,6 +205,9 @@ main = getArgs >>= \args ->
                       "--wired-in-deprecations"
                          -> putStr (gen_wired_in_deprecations p_o_specs)
 
+                      "--foundation-tests"
+                         -> putStr (gen_foundation_tests p_o_specs)
+
                       _ -> error "Should not happen, known_args out of sync?"
                    )
 
@@ -229,7 +233,8 @@ known_args
        "--make-haskell-source",
        "--make-latex-doc",
        "--wired-in-docs",
-       "--wired-in-deprecations"
+       "--wired-in-deprecations",
+       "--foundation-tests"
      ]
 
 ------------------------------------------------------------------
@@ -679,6 +684,72 @@ gen_wired_in_deprecations (Info _ entries)
         | otherwise = Nothing
 
 
+gen_foundation_tests :: Info -> String
+gen_foundation_tests (Info _ entries)
+  = "tests =\n  [ "
+    ++ intercalate "\n  , " (catMaybes $ map mkTest entries)
+    ++ "\n  ]\n"
+    ++ "\n" ++ intercalate "\n" (map mkInstances testable_tys)
+  where
+    testable_tys = nub (sort (mapMaybe (\po -> ty po <$ mkTest po) entries))
+
+    mkInstances ty = unlines $
+      [ "instance TestPrimop (" ++ pprTy ty ++ ") where"
+      , "  testPrimop s l r = Property s $ \\ " ++ intercalate " " (zipWith mkArg [0..] (args ty)) ++ " -> " ++ mk_body "l" ++ " === " ++ mk_body "r" ]
+
+      where
+        n_args = length (args ty)
+
+        mk_body s = res_ty ty (" (" ++ s ++ " " ++ intercalate " " vs ++ ")")
+
+        vs = zipWith (\n _ -> "x" ++ show n) [0..] (args ty)
+
+    mkArg n t = "(" ++ unwrapper t  ++ "-> x" ++ show n ++ ")"
+
+
+    wrapper s = "w" ++ s
+    unwrapper s = "u" ++ s
+
+
+    args (TyF (TyApp (TyCon c) []) t2) = c : args t2
+    args (TyApp {}) = []
+    args (TyUTup {}) = []
+
+    res_ty (TyF _ t2) x = res_ty t2 x
+    res_ty (TyApp (TyCon c) []) x = wrapper c ++ x
+    res_ty (TyUTup args) x =
+      let wtup = case length args of
+                   2 -> "WTUP2"
+                   3 -> "WTUP3"
+      in wtup ++"(" ++ intercalate "," (map (\a -> res_ty a "") args ++ [x]) ++ ")"
+
+
+
+    wrap qual nm | isLower (head nm) = qual ++ "." ++ nm
+            | otherwise = "(" ++ qual ++ "." ++ nm ++ ")"
+    mkTest po
+      | Just poName <- getName po
+      , is_primop po
+      , not $ is_vector po
+      , poName /= "tagToEnum#"
+      , poName /= "quotRemWord2#"
+      , (testable (ty po))
+      = Just $ intercalate " " ["testPrimop", "\"" ++ poName ++ "\"", wrap "Primop" poName, wrap "Wrapper" poName]
+      | otherwise = Nothing
+
+
+
+    testable (TyF t1 t2) = testable t1 && testable t2
+    testable (TyC _  t2) = testable t2
+    testable (TyApp tc tys) = testableTyCon tc && all testable tys
+    testable (TyVar a)   = False
+    testable (TyUTup tys)  = all testable tys
+
+    testableTyCon (TyCon c) =
+      c `elem` ["Int#", "Word#", "Word8#", "Word16#", "Word32#", "Word64#"
+               , "Int8#", "Int16#", "Int32#", "Int64#", "Char#"]
+    testableTyCon _ = False
+
 ------------------------------------------------------------------
 -- Create PrimOpInfo text from PrimOpSpecs -----------------------
 ------------------------------------------------------------------


=====================================
utils/genprimopcode/Syntax.hs
=====================================
@@ -78,7 +78,7 @@ data Ty
    | TyVar  TyVar
    | TyUTup [Ty]   -- unboxed tuples; just a TyCon really,
                    -- but convenient like this
-   deriving (Eq,Show)
+   deriving (Eq,Show, Ord)
 
 type TyVar = String
 type TyVarBinder = String



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a10aa396d536e587650f0160b8db2133eeecc243

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a10aa396d536e587650f0160b8db2133eeecc243
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250225/f0be7898/attachment-0001.html>


More information about the ghc-commits mailing list