
All the same issues arise for Int# too, right? I guess you're right :) I removed the rules for wrappers (eqInteger) and created rules for "primOps" (eqIntegerPrim, which I think I'll rename to eqInteger#)
Why? Because eqInteger is now inlined, so the rule doesn't get a chance to fire? There's something very subtle going on with inlining and I can't grasp what it is. At the moment I have this in prelude/PrelNames.lhs:
eqIntegerPrimIdKey = mkPreludeMiscIdUnique 70 eqIntegerPrimName = varQual gHC_INTEGER_TYPE (fsLit "eqIntegerPrim") eqIntegerPrimIdKey and in prelude/PrelRules.lhs I have this: builtinIntegerRules = [ ... rule_binop_Prim "eqIntegerPrim" eqIntegerPrimName (==), ...] where rule_binop_Prim str name op = BuiltinRule { ru_name = fsLit str, ru_fn = name, ru_nargs = 2, ru_try = match_Integer_binop_Prim op } match_Integer_binop_Prim binop dflags _ id_unf [xl, yl] | Just (LitInteger x _) <- exprIsLiteral_maybe id_unf xl , Just (LitInteger y _) <- exprIsLiteral_maybe id_unf yl = Just (if x `binop` y then trueValInt dflags else falseValInt dflags) match_Integer_binop_Prim _ _ _ _ _ = Nothing My understanding is that this rule will fire if it finds a function "eqIntegerPrim" with two Integer literals as parameters. Given my definitions in integer-gmp library: {-# NOINLINE eqIntegerPrim #-} eqIntegerPrim :: Integer -> Integer -> Int# eqIntegerPrim ... -- same as before, but uses new primops {-# INLINE eqInteger #-} eqInteger :: Integer -> Integer -> Bool eqInteger a b = tagToEnum# (a `eqIntegerPrim` b) my understanding is that in expression: eqIntegerE = (100012 :: Integer) == 100012 the (==) gets inlined to eqInteger: eqIntegerE = (100012 :: Integer) `eqInteger` 100012 which in turn gets inlined to eqIntegerPrim: eqIntegerE = tagToEnum# ((100012 :: Integer) `eqIntegerPrim` 100012) At this point inling stops (because of NOINLINE) and my rule fires giving: eqIntegerE = tagToEnum# 1# which in turns allows the rule for tagToEnum# to fire, giving: eqIntegerE = GHC.Prim.True Now here's the tricky part. I'm testing this with test lib/integer/integerConstantFolding in the testsuite and the test fails because rules for quotRemInteger, divModInteger, quotInteger and remInteger don't fire, leaving the constants unfolded. I noticed that if I mark eqInteger with NOINLINE, then these rules fire, but then obviously comparisons like (100012 :: Integer) == 100012 don't get folded and the test fails anyway. I'm analyzing how the function quotInteger and others use eqInteger, but I don't see anything that would be obvious. Janek