[commit: ghc] master: Add -fwarn-redundant-constrains to test for #9708 (2c6fe5b)

git at git.haskell.org git at git.haskell.org
Sun Jan 24 19:32:55 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/2c6fe5b8a854f06ea9574f7dca545b4c2d35b811/ghc

>---------------------------------------------------------------

commit 2c6fe5b8a854f06ea9574f7dca545b4c2d35b811
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Sun Jan 24 02:49:42 2016 +0100

    Add -fwarn-redundant-constrains to test for #9708
    
    Fixes validate on Travis.
    
    Reviewed by: bgamari
    
    Differential Revision: https://phabricator.haskell.org/D1834


>---------------------------------------------------------------

2c6fe5b8a854f06ea9574f7dca545b4c2d35b811
 testsuite/tests/typecheck/should_compile/T9708.hs     | 9 +++++++++
 testsuite/tests/typecheck/should_compile/T9708.stderr | 0
 2 files changed, 9 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T9708.hs b/testsuite/tests/typecheck/should_compile/T9708.hs
index cb0e847..3878857 100644
--- a/testsuite/tests/typecheck/should_compile/T9708.hs
+++ b/testsuite/tests/typecheck/should_compile/T9708.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE DataKinds, TypeOperators, TypeFamilies #-}
+{-# OPTIONS_GHC -fwarn-redundant-constraints #-}
 module TcTypeNatSimple where
 
 import GHC.TypeLits
@@ -16,5 +17,13 @@ type family SomeFun (n :: Nat)
 -- with the change to stop Deriveds from rewriting Deriveds (around Dec. 12, 2014),
 -- this failed again
 
+-- 2016-01-23: it just started passing again, when
+-- -fwarn-redundant-constraints was removed from the default warning set.
+-- Turning the warning back on for this module, ghc reports (and probably has
+-- for some time):
+--      Redundant constraints: (x <= y, y <= x)
+--      In the type signature for:
+--            ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> ()
+
 ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> ()
 ti7 _ _ = ()
diff --git a/testsuite/tests/typecheck/should_compile/T9708.stderr b/testsuite/tests/typecheck/should_compile/T9708.stderr
deleted file mode 100644
index e69de29..0000000



More information about the ghc-commits mailing list