[Git][ghc/ghc][wip/backports-9.6] Enable -Wstar-is-type by default (#22759)

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Thu Jan 26 21:06:47 UTC 2023



Ben Gamari pushed to branch wip/backports-9.6 at Glasgow Haskell Compiler / GHC


Commits:
1afaf7ce by Vladislav Zavialov at 2023-01-26T16:06:35-05:00
Enable -Wstar-is-type by default (#22759)

Following the plan in GHC Proposal #143 "Remove the * kind syntax",
which states:

	In the next release (or 3 years in), enable -fwarn-star-is-type by default.

The "next release" happens to be 9.6.1

I also moved the T21583 test case from should_fail to should_compile,
because the only reason it was failing was -Werror=compat in our test
suite configuration.

(cherry picked from commit e9c0537cfbf7b47c64f592f529e402358b66ca7f)

- - - - -


15 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Tc/Errors/Types.hs
- docs/users_guide/9.6.1-notes.rst
- docs/users_guide/using-warnings.rst
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/typecheck/should_fail/T21583.hs → testsuite/tests/typecheck/should_compile/T21583.hs
- testsuite/tests/typecheck/should_fail/T21583.stderr → testsuite/tests/typecheck/should_compile/T21583.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/all.T
- + testsuite/tests/warnings/should_compile/T22759.hs
- + testsuite/tests/warnings/should_compile/T22759.stderr
- testsuite/tests/warnings/should_compile/all.T
- testsuite/tests/wcompat-warnings/Template.hs
- testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -820,6 +820,7 @@ standardWarnings -- see Note [Documenting warning flags]
         Opt_WarnUnrecognisedWarningFlags,
         Opt_WarnSimplifiableClassConstraints,
         Opt_WarnStarBinder,
+        Opt_WarnStarIsType,
         Opt_WarnInaccessibleCode,
         Opt_WarnSpaceAfterBang,
         Opt_WarnNonCanonicalMonadInstances,
@@ -861,7 +862,6 @@ minusWallOpts
         Opt_WarnMissingPatternSynonymSignatures,
         Opt_WarnUnusedRecordWildcards,
         Opt_WarnRedundantRecordWildcards,
-        Opt_WarnStarIsType,
         Opt_WarnIncompleteUniPatterns,
         Opt_WarnIncompletePatternsRecUpd
       ]
@@ -879,7 +879,6 @@ minusWcompatOpts :: [WarningFlag]
 minusWcompatOpts
     = [ Opt_WarnSemigroup
       , Opt_WarnNonCanonicalMonoidInstances
-      , Opt_WarnStarIsType
       , Opt_WarnCompatUnqualifiedImports
       , Opt_WarnTypeEqualityOutOfScope
       ]


=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -2567,7 +2567,7 @@ data TcRnMessage where
          testsuite/tests/typecheck/should_compile/tc078
          testsuite/tests/typecheck/should_compile/tc161
          testsuite/tests/typecheck/should_fail/T5051
-         testsuite/tests/typecheck/should_fail/T21583
+         testsuite/tests/typecheck/should_compile/T21583
          testsuite/tests/backpack/should_compile/bkp47
          testsuite/tests/backpack/should_fail/bkpfail25
          testsuite/tests/parser/should_compile/T2245


=====================================
docs/users_guide/9.6.1-notes.rst
=====================================
@@ -96,6 +96,10 @@ Compiler
 - The :ghc-flag:`-Woperator-whitespace` warning no longer ignores constructor symbols
   (operators starting with ``:``).
 
+- The :ghc-flag:`-Wstar-is-type` warning is now enabled by default, continuing
+  the implementation of GHC proposal `#143
+  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0143-remove-star-kind.rst>`_.
+
 GHCi
 ~~~~
 


=====================================
docs/users_guide/using-warnings.rst
=====================================
@@ -60,6 +60,7 @@ To reverse ``-Werror``, which makes all warnings into errors, use ``-Wwarn``.
         * :ghc-flag:`-Wunrecognised-warning-flags`
         * :ghc-flag:`-Winaccessible-code`
         * :ghc-flag:`-Wstar-binder`
+        * :ghc-flag:`-Wstar-is-type`
         * :ghc-flag:`-Woperator-whitespace-ext-conflict`
         * :ghc-flag:`-Wambiguous-fields`
         * :ghc-flag:`-Wunicode-bidirectional-format-characters`
@@ -160,7 +161,6 @@ The following flags are simple ways to select standard "packages" of warnings:
 
         * :ghc-flag:`-Wsemigroup`
         * :ghc-flag:`-Wnoncanonical-monoid-instances`
-        * :ghc-flag:`-Wstar-is-type`
         * :ghc-flag:`-Wcompat-unqualified-imports`
         * :ghc-flag:`-Wtype-equality-out-of-scope`
 
@@ -1505,9 +1505,6 @@ of ``-W(no-)*``.
      breaking change takes place. The recommended fix is to replace ``*`` with
      ``Type`` imported from ``Data.Kind``.
 
-     Being part of the :ghc-flag:`-Wcompat` option group, this warning is off by
-     default, but will be switched on in a future GHC release.
-
 .. ghc-flag:: -Wstar-binder
      :shortdesc: warn about binding the ``(*)`` type operator despite
          :extension:`StarIsType`


=====================================
testsuite/tests/ghci/scripts/ghci024.stdout
=====================================
@@ -16,7 +16,6 @@ other dynamic, non-language, flag settings:
   -fprefer-byte-code
 warning settings:
   -Wsemigroup
-  -Wstar-is-type
   -Wcompat-unqualified-imports
   -Wtype-equality-out-of-scope
 ~~~~~~~~~~ Testing :set -a


=====================================
testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
=====================================
@@ -15,7 +15,6 @@ other dynamic, non-language, flag settings:
   -fprefer-byte-code
 warning settings:
   -Wsemigroup
-  -Wstar-is-type
   -Wcompat-unqualified-imports
   -Wtype-equality-out-of-scope
 ~~~~~~~~~~ Testing :set -a


=====================================
testsuite/tests/typecheck/should_fail/T21583.hs → testsuite/tests/typecheck/should_compile/T21583.hs
=====================================
@@ -5,13 +5,15 @@
 {-# LANGUAGE FlexibleContexts #-}
 module Telomare.Possible where
 
+import Data.Kind (Type)
+
 data PartExprF f
   = ZeroSF
   deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
 
 newtype EnhancedExpr f = EnhancedExpr {unEnhanceExpr :: SplitFunctor f PartExprF (EnhancedExpr f)} -- deriving (Eq, Show)
 
-type family Base t :: * -> *
+type family Base t :: Type -> Type
 
 type instance Base (EnhancedExpr f) = SplitFunctor f PartExprF
 


=====================================
testsuite/tests/typecheck/should_fail/T21583.stderr → testsuite/tests/typecheck/should_compile/T21583.stderr
=====================================
@@ -1,27 +1,15 @@
 
-T21583.hs:14:23: error: [GHC-39567] [-Wstar-is-type (in -Wall, -Wcompat), Werror=star-is-type]
-    Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’
-    relies on the StarIsType extension, which will become
-    deprecated in the future.
-    Suggested fix: Use ‘Type’ from ‘Data.Kind’ instead.
-
-T21583.hs:14:28: error: [GHC-39567] [-Wstar-is-type (in -Wall, -Wcompat), Werror=star-is-type]
-    Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’
-    relies on the StarIsType extension, which will become
-    deprecated in the future.
-    Suggested fix: Use ‘Type’ from ‘Data.Kind’ instead.
-
-T21583.hs:56:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)]
+T21583.hs:58:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)]
     • No explicit implementation for
         ‘fmap’
     • In the instance declaration for ‘Functor (SplitFunctor g f)’
 
-T21583.hs:58:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)]
+T21583.hs:60:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)]
     • No explicit implementation for
         either ‘foldMap’ or ‘foldr’
     • In the instance declaration for ‘Foldable (SplitFunctor g f)’
 
-T21583.hs:60:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)]
+T21583.hs:62:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)]
     • No explicit implementation for
         either ‘traverse’ or ‘sequenceA’
     • In the instance declaration for ‘Traversable (SplitFunctor g f)’


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -827,6 +827,7 @@ test('T21328', normal, compile, [''])
 test('T21516', normal, compile, [''])
 test('T21519', normal, compile, [''])
 test('T21519a', normal, compile, [''])
+test('T21583', normal, compile, [''])
 test('T2595', normal, compile, [''])
 test('T3632', normal, compile, [''])
 test('T10808', normal, compile, [''])


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -660,7 +660,6 @@ test('T20768_fail', normal, compile_fail, [''])
 test('T21327', normal, compile_fail, [''])
 test('T21338', normal, compile_fail, [''])
 test('T21158', normal, compile_fail, [''])
-test('T21583', normal, compile_fail, [''])
 test('MissingDefaultMethodBinding', normal, compile_fail, [''])
 test('T21447', normal, compile_fail, [''])
 test('T21530a', normal, compile_fail, [''])


=====================================
testsuite/tests/warnings/should_compile/T22759.hs
=====================================
@@ -0,0 +1,4 @@
+module T22759 where
+
+b :: (Bool :: *)
+b = True
\ No newline at end of file


=====================================
testsuite/tests/warnings/should_compile/T22759.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T22759.hs:3:15: warning: [GHC-39567] [-Wstar-is-type (in -Wdefault)]
+    Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’
+    relies on the StarIsType extension, which will become
+    deprecated in the future.
+    Suggested fix: Use ‘Type’ from ‘Data.Kind’ instead.


=====================================
testsuite/tests/warnings/should_compile/all.T
=====================================
@@ -54,3 +54,4 @@ test('T18862a', normal, compile, [''])
 test('T18862b', normal, compile, [''])
 test('T20312', normal, compile,['-Wall'])
 test('T22676', [extra_files(['src'])], multimod_compile, ['src.hs', '-working-dir src -Wmissing-home-modules -v0'])
+test('T22759', normal, compile, [''])


=====================================
testsuite/tests/wcompat-warnings/Template.hs
=====================================
@@ -1,5 +1,3 @@
-{-# LANGUAGE KindSignatures #-}
-
 module WCompatWarningsOnOff where
 
 import qualified Data.Semigroup as Semi
@@ -15,7 +13,3 @@ instance Semi.Semigroup S where
 instance Monoid S where
   S a `mappend` S b = S (a+b)
   mempty = S 0
-
--- -fwarn-star-is-type
-b :: (Bool :: *)
-b = True


=====================================
testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
=====================================
@@ -1,23 +1,17 @@
 
-Template.hs:7:1: warning: [-Wsemigroup (in -Wcompat)]
+Template.hs:5:1: warning: [-Wsemigroup (in -Wcompat)]
     Local definition of ‘<>’ clashes with a future Prelude name.
     This will become an error in a future release.
 
-Template.hs:13:3: warning: [-Wnoncanonical-monoid-instances (in -Wdefault, -Wcompat)]
+Template.hs:11:3: warning: [-Wnoncanonical-monoid-instances (in -Wdefault, -Wcompat)]
     Noncanonical ‘(<>) = mappend’ definition detected
     in the instance declaration for ‘Semigroup S’.
     Move definition from ‘mappend’ to ‘(<>)’
     See also: https://gitlab.haskell.org/ghc/ghc/-/wikis/proposal/semigroup-monoid
 
-Template.hs:16:3: warning: [-Wnoncanonical-monoid-instances (in -Wdefault, -Wcompat)]
+Template.hs:14:3: warning: [-Wnoncanonical-monoid-instances (in -Wdefault, -Wcompat)]
     Noncanonical ‘mappend’ definition detected
     in the instance declaration for ‘Monoid S’.
     ‘mappend’ will eventually be removed in favour of ‘(<>)’
     Either remove definition for ‘mappend’ (recommended) or define as ‘mappend = (<>)’
     See also: https://gitlab.haskell.org/ghc/ghc/-/wikis/proposal/semigroup-monoid
-
-Template.hs:20:15: warning: [GHC-39567] [-Wstar-is-type (in -Wall, -Wcompat)]
-    Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’
-    relies on the StarIsType extension, which will become
-    deprecated in the future.
-    Suggested fix: Use ‘Type’ from ‘Data.Kind’ instead.



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1afaf7ce634a7346bb1cf7521338c8609e3921db
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/20230126/62507e06/attachment-0001.html>


More information about the ghc-commits mailing list