summaryrefslogtreecommitdiff
path: root/testsuite/tests/simplCore
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2015-07-24 12:50:42 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2015-07-27 14:02:33 +0100
commit2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4 (patch)
tree8a7819918d5a8e8fc69c3c036fb3c7670498cb84 /testsuite/tests/simplCore
parentbc4b64ca5b99bff6b3d5051b57cb2bc52bd4c841 (diff)
downloadhaskell-2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4.tar.gz
Improve warnings for rules that might not fire
Two main things here * Previously we only warned about the "head" function of the rule, but actually the warning applies to any free variable on the LHS. * We now warn not only when one of these free vars can inline, but also if it has an active RULE (c.f. Trac #10528) See Note [Rules and inlining/other rules] in Desugar This actually shows up quite a few warnings in the libraries, notably in Control.Arrow, where it correctly points out that rules like "compose/arr" forall f g . (arr f) . (arr g) = arr (f . g) might never fire, because the rule for 'arr' (dictionary selection) might fire first. I'm not really sure what to do here; there is some discussion in Trac #10595. A minor change is adding BasicTypes.pprRuleName to pretty-print RuleName.
Diffstat (limited to 'testsuite/tests/simplCore')
-rw-r--r--testsuite/tests/simplCore/should_compile/T5776.hs16
-rw-r--r--testsuite/tests/simplCore/should_compile/T6082-RULE.stderr8
-rw-r--r--testsuite/tests/simplCore/should_compile/T7287.hs11
3 files changed, 25 insertions, 10 deletions
diff --git a/testsuite/tests/simplCore/should_compile/T5776.hs b/testsuite/tests/simplCore/should_compile/T5776.hs
index df6444f25a..17a3e25852 100644
--- a/testsuite/tests/simplCore/should_compile/T5776.hs
+++ b/testsuite/tests/simplCore/should_compile/T5776.hs
@@ -3,26 +3,30 @@ module T5776 where
-- The point about this test is that we should get a rule like this:
-- "foo" [ALWAYS]
-- forall (@ a)
--- ($dEq :: GHC.Classes.Eq a)
--- ($dEq1 :: GHC.Classes.Eq a)
+-- ($dEq :: Eq a)
+-- ($dEq1 :: Eq a)
-- (x :: a)
-- (y :: a)
-- (z :: a).
--- T5776.f (GHC.Classes.== @ a $dEq1 x y)
--- (GHC.Classes.== @ a $dEq y z)
+-- T5776.f (g @ a $dEq1 x y)
+-- (g @ a $dEq y z)
-- = GHC.Types.True
--
-- Note the *two* forall'd dEq parameters. This is important.
-- See Note [Simplifying RULE lhs constraints] in TcSimplify
{-# RULES "foo" forall x y z.
- f (x == y) (y == z) = True
+ f (g x y) (g y z) = True
#-}
+g :: Eq a => a -> a -> Bool
+{-# NOINLINE g #-}
+g = (==)
+
f :: Bool -> Bool -> Bool
{-# NOINLINE f #-}
f a b = False
blah :: Int -> Int -> Bool
-blah x y = f (x==y) (x==y)
+blah x y = f (g x y) (g x y)
diff --git a/testsuite/tests/simplCore/should_compile/T6082-RULE.stderr b/testsuite/tests/simplCore/should_compile/T6082-RULE.stderr
index f619687151..165a7773bb 100644
--- a/testsuite/tests/simplCore/should_compile/T6082-RULE.stderr
+++ b/testsuite/tests/simplCore/should_compile/T6082-RULE.stderr
@@ -1,8 +1,8 @@
-T6082-RULE.hs:5:11: Warning:
+T6082-RULE.hs:5:11: warning:
Rule "foo1" may never fire because ‘foo1’ might inline first
- Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ‘foo1’
+ Probable fix: add an INLINE[n] or NOINLINE[n] pragma for ‘foo1’
-T6082-RULE.hs:10:11: Warning:
+T6082-RULE.hs:10:11: warning:
Rule "foo2" may never fire because ‘foo2’ might inline first
- Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ‘foo2’
+ Probable fix: add an INLINE[n] or NOINLINE[n] pragma for ‘foo2’
diff --git a/testsuite/tests/simplCore/should_compile/T7287.hs b/testsuite/tests/simplCore/should_compile/T7287.hs
index 1d777bdf9e..2768fb593d 100644
--- a/testsuite/tests/simplCore/should_compile/T7287.hs
+++ b/testsuite/tests/simplCore/should_compile/T7287.hs
@@ -6,3 +6,14 @@ import GHC.Prim
{-# RULES
"int2Word#/word2Int#" forall x. int2Word# (word2Int# x) = x
#-}
+
+{- We get a legitmiate
+
+ T7287.hs:7:3: warning:
+ Rule int2Word#/word2Int# may never fire because
+ rule "word2Int#" for ‘word2Int#’ might fire first
+ Probable fix: add phase [n] or [~n] to the competing rule
+
+because rule "word2Int#" is the constant folding rule that converts
+a sufficiently-narrow Word# literal to an Int#. There is a similar
+one for int2Word#, so the whole lot is confluent. -} \ No newline at end of file