[commit: ghc] master: testsuite: Deduplicate source in wcompat-warnings test (92db10b)

git at git.haskell.org git at git.haskell.org
Tue Aug 21 22:57:22 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/92db10bc061e0054d0a7504de420b5ad7f72a0a0/ghc

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

commit 92db10bc061e0054d0a7504de420b5ad7f72a0a0
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Aug 21 12:48:34 2018 -0400

    testsuite: Deduplicate source in wcompat-warnings test


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

92db10bc061e0054d0a7504de420b5ad7f72a0a0
 .../{WCompatWarningsOnOff.hs => Template.hs}       |  5 +----
 .../tests/wcompat-warnings/WCompatWarningsNotOn.hs | 25 ++-------------------
 .../tests/wcompat-warnings/WCompatWarningsOff.hs   | 26 +++-------------------
 .../tests/wcompat-warnings/WCompatWarningsOn.hs    | 26 +++-------------------
 .../wcompat-warnings/WCompatWarningsOn.stderr      | 10 ++++-----
 .../tests/wcompat-warnings/WCompatWarningsOnOff.hs | 26 +++-------------------
 testsuite/tests/wcompat-warnings/all.T             |  9 ++++----
 7 files changed, 22 insertions(+), 105 deletions(-)

diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs b/testsuite/tests/wcompat-warnings/Template.hs
similarity index 74%
copy from testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs
copy to testsuite/tests/wcompat-warnings/Template.hs
index 81df757..e3423c8 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs
+++ b/testsuite/tests/wcompat-warnings/Template.hs
@@ -1,8 +1,4 @@
--- Test purpose:
--- Ensure that -Wno-compat disables a previously set -Wcompat
 {-# LANGUAGE NoMonadFailDesugaring #-}
-{-# OPTIONS_GHC -Wcompat #-}
-{-# OPTIONS_GHC -Wno-compat #-}
 
 module WCompatWarningsOnOff where
 
@@ -24,3 +20,4 @@ instance Semi.Semigroup S where
 instance Monoid S where
   S a `mappend` S b = S (a+b)
   mempty = S 0
+
diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsNotOn.hs b/testsuite/tests/wcompat-warnings/WCompatWarningsNotOn.hs
index a26c565..7cd6a42 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsNotOn.hs
+++ b/testsuite/tests/wcompat-warnings/WCompatWarningsNotOn.hs
@@ -1,26 +1,5 @@
 -- Test purpose:
 -- Ensure that not using -Wcompat does not enable its warnings
-{-# LANGUAGE NoMonadFailDesugaring #-}
--- {-# OPTIONS_GHC -Wcompat #-}
--- {-# OPTIONS_GHC -Wno-compat #-}
 
-module WCompatWarningsNotOn where
-
-import qualified Data.Semigroup as Semi
-
-monadFail :: Monad m => m a
-monadFail = do
-    Just _ <- undefined
-    undefined
-
-(<>) = undefined -- Semigroup warnings
-
--- -fwarn-noncanonical-monoid-instances
-newtype S = S Int
-
-instance Semi.Semigroup S where
-  (<>) = mappend
-
-instance Monoid S where
-  S a `mappend` S b = S (a+b)
-  mempty = S 0
+{-# LANGUAGE CPP #-}
+#include "Template.hs"
diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOff.hs b/testsuite/tests/wcompat-warnings/WCompatWarningsOff.hs
index 33c26cc..637fbb3 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsOff.hs
+++ b/testsuite/tests/wcompat-warnings/WCompatWarningsOff.hs
@@ -1,26 +1,6 @@
 -- Test purpose:
 -- Ensure that using -Wno-compat does not switch on warnings
-{-# LANGUAGE NoMonadFailDesugaring #-}
--- {-# OPTIONS_GHC -Wcompat #-}
-{-# OPTIONS_GHC -Wno-compat #-}
-
-module WCompatWarningsOff where
-
-import qualified Data.Semigroup as Semi
-
-monadFail :: Monad m => m a
-monadFail = do
-    Just _ <- undefined
-    undefined
 
-(<>) = undefined -- Semigroup warnings
-
--- -fwarn-noncanonical-monoid-instances
-newtype S = S Int
-
-instance Semi.Semigroup S where
-  (<>) = mappend
-
-instance Monoid S where
-  S a `mappend` S b = S (a+b)
-  mempty = S 0
+{-# OPTIONS_GHC -Wno-compat #-}
+{-# LANGUAGE CPP #-}
+#include "Template.hs"
diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.hs b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.hs
index 7d9e7de..9c75982 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.hs
+++ b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.hs
@@ -1,26 +1,6 @@
 -- Test purpose:
 -- Ensure that -Wcompat switches on the right warnings
-{-# LANGUAGE NoMonadFailDesugaring #-}
-{-# OPTIONS_GHC -Wcompat #-}
--- {-# OPTIONS_GHC -Wno-compat #-}
-
-module WCompatWarningsOn where
-
-import qualified Data.Semigroup as Semi
-
-monadFail :: Monad m => m a
-monadFail = do
-    Just _ <- undefined
-    undefined
 
-(<>) = undefined -- Semigroup warnings
-
--- -fwarn-noncanonical-monoid-instances
-newtype S = S Int
-
-instance Semi.Semigroup S where
-  (<>) = mappend
-
-instance Monoid S where
-  S a `mappend` S b = S (a+b)
-  mempty = S 0
+{-# OPTIONS_GHC -Wcompat #-}
+{-# LANGUAGE CPP #-}
+#include "Template.hs"
diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
index c62780f..5c2d9c5 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
+++ b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
@@ -1,12 +1,12 @@
 
-WCompatWarningsOn.hs:13:5: warning: [-Wmissing-monadfail-instances (in -Wcompat)]
+Template.hs:9:5: warning: [-Wmissing-monadfail-instances (in -Wcompat)]
     • Could not deduce (Control.Monad.Fail.MonadFail m)
         arising from the failable pattern ‘Just _’
         (this will become an error in a future GHC release)
       from the context: Monad m
         bound by the type signature for:
                    monadFail :: forall (m :: * -> *) a. Monad m => m a
-        at WCompatWarningsOn.hs:11:1-27
+        at Template.hs:7:1-27
       Possible fix:
         add (Control.Monad.Fail.MonadFail m) to the context of
           the type signature for:
@@ -20,16 +20,16 @@ WCompatWarningsOn.hs:13:5: warning: [-Wmissing-monadfail-instances (in -Wcompat)
             = do Just _ <- undefined
                  undefined
 
-WCompatWarningsOn.hs:16:1: warning: [-Wsemigroup (in -Wcompat)]
+Template.hs:12:1: warning: [-Wsemigroup (in -Wcompat)]
     Local definition of ‘<>’ clashes with a future Prelude name.
     This will become an error in a future release.
 
-WCompatWarningsOn.hs:22:3: warning: [-Wnoncanonical-monoid-instances (in -Wcompat)]
+Template.hs:18:3: warning: [-Wnoncanonical-monoid-instances (in -Wcompat)]
     Noncanonical ‘(<>) = mappend’ definition detected
     in the instance declaration for ‘Semigroup S’.
     Move definition from ‘mappend’ to ‘(<>)’
 
-WCompatWarningsOn.hs:25:3: warning: [-Wnoncanonical-monoid-instances (in -Wcompat)]
+Template.hs:21:3: warning: [-Wnoncanonical-monoid-instances (in -Wcompat)]
     Noncanonical ‘mappend’ definition detected
     in the instance declaration for ‘Monoid S’.
     Define as ‘mappend = (<>)’
diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs b/testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs
index 81df757..d644568 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs
+++ b/testsuite/tests/wcompat-warnings/WCompatWarningsOnOff.hs
@@ -1,26 +1,6 @@
 -- Test purpose:
 -- Ensure that -Wno-compat disables a previously set -Wcompat
-{-# LANGUAGE NoMonadFailDesugaring #-}
-{-# OPTIONS_GHC -Wcompat #-}
-{-# OPTIONS_GHC -Wno-compat #-}
 
-module WCompatWarningsOnOff where
-
-import qualified Data.Semigroup as Semi
-
-monadFail :: Monad m => m a
-monadFail = do
-    Just _ <- undefined
-    undefined
-
-(<>) = undefined -- Semigroup warnings
-
--- -fwarn-noncanonical-monoid-instances
-newtype S = S Int
-
-instance Semi.Semigroup S where
-  (<>) = mappend
-
-instance Monoid S where
-  S a `mappend` S b = S (a+b)
-  mempty = S 0
+{-# OPTIONS_GHC -Wcompat -Wno-compat #-}
+{-# LANGUAGE CPP #-}
+#include "Template.hs"
diff --git a/testsuite/tests/wcompat-warnings/all.T b/testsuite/tests/wcompat-warnings/all.T
index 4447f99..5d62466 100644
--- a/testsuite/tests/wcompat-warnings/all.T
+++ b/testsuite/tests/wcompat-warnings/all.T
@@ -1,4 +1,5 @@
-test('WCompatWarningsOn',    normal, compile, [''])
-test('WCompatWarningsOff',   normal, compile, [''])
-test('WCompatWarningsNotOn', normal, compile, [''])
-test('WCompatWarningsOnOff', normal, compile, [''])
+# N.B. the source files are all stubs; edit Template.hs
+test('WCompatWarningsOn',    extra_files(['Template.hs']), compile, [''])
+test('WCompatWarningsOff',   extra_files(['Template.hs']), compile, [''])
+test('WCompatWarningsNotOn', extra_files(['Template.hs']), compile, [''])
+test('WCompatWarningsOnOff', extra_files(['Template.hs']), compile, [''])



More information about the ghc-commits mailing list