diff options
-rw-r--r-- | compiler/hsSyn/PlaceHolder.hs | 12 | ||||
-rw-r--r-- | compiler/main/DynFlags.hs | 5 | ||||
-rw-r--r-- | compiler/rename/RnEnv.hs | 10 | ||||
-rw-r--r-- | compiler/rename/RnSource.hs | 6 | ||||
-rw-r--r-- | compiler/rename/RnTypes.hs | 2 | ||||
-rw-r--r-- | docs/users_guide/8.0.1-notes.rst | 18 | ||||
-rw-r--r-- | docs/users_guide/glasgow_exts.rst | 28 | ||||
-rw-r--r-- | docs/users_guide/using-warnings.rst | 46 | ||||
-rw-r--r-- | libraries/base/Data/Either.hs | 4 | ||||
-rw-r--r-- | libraries/base/Data/Type/Bool.hs | 12 | ||||
-rw-r--r-- | libraries/base/Data/Type/Equality.hs | 16 | ||||
-rw-r--r-- | libraries/base/GHC/Generics.hs | 28 | ||||
-rw-r--r-- | libraries/base/GHC/TypeLits.hs | 8 | ||||
-rw-r--r-- | testsuite/tests/determinism/should_compile/determ004.hs | 6 | ||||
-rw-r--r-- | testsuite/tests/indexed-types/should_compile/all.T | 4 | ||||
-rw-r--r-- | testsuite/tests/simplCore/should_compile/T10689a.hs | 4 | ||||
-rw-r--r-- | utils/mkUserGuidePart/Options/Warnings.hs | 12 |
17 files changed, 150 insertions, 71 deletions
diff --git a/compiler/hsSyn/PlaceHolder.hs b/compiler/hsSyn/PlaceHolder.hs index 004f465d76..87736ac3d0 100644 --- a/compiler/hsSyn/PlaceHolder.hs +++ b/compiler/hsSyn/PlaceHolder.hs @@ -37,15 +37,15 @@ data PlaceHolder = PlaceHolder -- | Types that are not defined until after type checking type family PostTc it ty :: * -- Note [Pass sensitive types] -type instance PostTc Id ty = ty -type instance PostTc Name _ty = PlaceHolder -type instance PostTc RdrName _ty = PlaceHolder +type instance PostTc Id ty = ty +type instance PostTc Name ty = PlaceHolder +type instance PostTc RdrName ty = PlaceHolder -- | Types that are not defined until after renaming type family PostRn id ty :: * -- Note [Pass sensitive types] -type instance PostRn Id ty = ty -type instance PostRn Name ty = ty -type instance PostRn RdrName _ty = PlaceHolder +type instance PostRn Id ty = ty +type instance PostRn Name ty = ty +type instance PostRn RdrName ty = PlaceHolder placeHolderKind :: PlaceHolder placeHolderKind = PlaceHolder diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index f6496d5fa6..22c2915960 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -562,6 +562,8 @@ data WarningFlag = | Opt_WarnUnusedPatternBinds | Opt_WarnUnusedImports | Opt_WarnUnusedMatches + | Opt_WarnUnusedTypePatterns + | Opt_WarnUnusedForalls | Opt_WarnContextQuantification -- remove in 8.2 | Opt_WarnWarningsDeprecations | Opt_WarnDeprecatedFlags @@ -2970,11 +2972,13 @@ wWarningFlags = [ flagSpec "unticked-promoted-constructors" Opt_WarnUntickedPromotedConstructors, flagSpec "unused-do-bind" Opt_WarnUnusedDoBind, + flagSpec "unused-foralls" Opt_WarnUnusedForalls, flagSpec "unused-imports" Opt_WarnUnusedImports, flagSpec "unused-local-binds" Opt_WarnUnusedLocalBinds, flagSpec "unused-matches" Opt_WarnUnusedMatches, flagSpec "unused-pattern-binds" Opt_WarnUnusedPatternBinds, flagSpec "unused-top-binds" Opt_WarnUnusedTopBinds, + flagSpec "unused-type-patterns" Opt_WarnUnusedTypePatterns, flagSpec "warnings-deprecations" Opt_WarnWarningsDeprecations, flagSpec "wrong-do-bind" Opt_WarnWrongDoBind, flagSpec "missing-pat-syn-sigs" Opt_WarnMissingPatSynSigs, @@ -3512,6 +3516,7 @@ minusWOpts Opt_WarnUnusedLocalBinds, Opt_WarnUnusedPatternBinds, Opt_WarnUnusedMatches, + Opt_WarnUnusedForalls, Opt_WarnUnusedImports, Opt_WarnIncompletePatterns, Opt_WarnDodgyExports, diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 0add967a35..d1ec1de6e6 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -41,7 +41,7 @@ module RnEnv ( checkDupNames, checkDupAndShadowedNames, dupNamesErr, checkTupSize, addFvRn, mapFvRn, mapMaybeFvRn, mapFvRnCPS, - warnUnusedMatches, + warnUnusedMatches, warnUnusedTypePatterns, warnUnusedTopBinds, warnUnusedLocalBinds, mkFieldEnv, dataTcOccs, kindSigErr, perhapsForallMsg, unknownSubordinateErr, @@ -2072,9 +2072,11 @@ warnUnusedTopBinds gres else gres warnUnusedGREs gres' -warnUnusedLocalBinds, warnUnusedMatches :: [Name] -> FreeVars -> RnM () -warnUnusedLocalBinds = check_unused Opt_WarnUnusedLocalBinds -warnUnusedMatches = check_unused Opt_WarnUnusedMatches +warnUnusedLocalBinds, warnUnusedMatches, warnUnusedTypePatterns + :: [Name] -> FreeVars -> RnM () +warnUnusedLocalBinds = check_unused Opt_WarnUnusedLocalBinds +warnUnusedMatches = check_unused Opt_WarnUnusedMatches +warnUnusedTypePatterns = check_unused Opt_WarnUnusedTypePatterns check_unused :: WarningFlag -> [Name] -> FreeVars -> RnM () check_unused flag bound_names used_names diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index ad5418a046..98aacd0467 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -729,7 +729,7 @@ rnFamInstDecl doc mb_cls tycon (HsIB { hsib_body = pats }) payload rnPayload -- appear *more than once* on the LHS -- e.g. F a Int a = Bool ; let tv_nms_used = extendNameSetList rhs_fvs tv_nms_dups - ; warnUnusedMatches var_names tv_nms_used + ; warnUnusedTypePatterns var_names tv_nms_used -- See Note [Renaming associated types] ; let bad_tvs = case mb_cls of @@ -854,7 +854,7 @@ fresh meta-variables whereas the former generate fresh skolems. Note [Unused type variables in family instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When the flag -fwarn-unused-matches is on, the compiler reports warnings +When the flag -fwarn-unused-type-patterns is on, the compiler reports warnings about unused type variables. (rnFamInstDecl) A type variable is considered used * when it is either occurs on the RHS of the family instance, or @@ -869,7 +869,7 @@ beginning with an underscore. Extra-constraints wild cards are not supported in type/data family instance declarations. -Relevant tickets: #3699, #10586 and #10982. +Relevant tickets: #3699, #10586, #10982 and #11451. Note [Renaming associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 0ddbf8ef0f..0d7f68c6b6 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1400,7 +1400,7 @@ inTypeDoc ty = text "In the type" <+> quotes (ppr ty) warnUnusedForAll :: SDoc -> LHsTyVarBndr Name -> FreeVars -> TcM () warnUnusedForAll in_doc (L loc tv) used_names - = whenWOptM Opt_WarnUnusedMatches $ + = whenWOptM Opt_WarnUnusedForalls $ unless (hsTyVarName tv `elemNameSet` used_names) $ addWarnAt loc $ vcat [ text "Unused quantified type variable" <+> quotes (ppr tv) diff --git a/docs/users_guide/8.0.1-notes.rst b/docs/users_guide/8.0.1-notes.rst index 6239ea5c52..b31223eef4 100644 --- a/docs/users_guide/8.0.1-notes.rst +++ b/docs/users_guide/8.0.1-notes.rst @@ -268,10 +268,20 @@ Compiler a warning when a pattern synonym definition doesn't have a type signature. It is turned off by default but enabled by :ghc-flag:`-Wall`. -- Changed the :ghc-flag:`-fwarn-unused-matches` flag to report unused type variables - in data and type families in addition to its previous behaviour. - To avoid warnings, unused type variables should be prefixed or replaced with - underscores. +- Added the :ghc-flag:`-Wunused-type-patterns` flag to report unused + type variables in data and type family instances. This flag is not implied + by :ghc-flag:`-Wall`, since :ghc-flag:`-Wunused-type-patterns` will + warn about unused type variables even if the types themselves are intended + to be used as documentation. If :ghc-flag:`-Wunused-type-patterns` is + enabled, one can prefix or replace unused type variables with underscores to + avoid warnings. + +- Split off the new flag :ghc-flag:`-Wunused-foralls` from the previously + existing flag :ghc-flag:`-Wunused-matches`. :ghc-flag:`-Wunused-foralls` + emits a warning in the specific case that a user writes explicit ``forall`` + syntax with unused type variables, while :ghc-flag:`-Wunused-matches` only + warns in the case of unused term-level patterns. Both flags are implied by + :ghc-flag:`-W`. - Added the :ghc-flag:`-Wtoo-many-guards` flag. When enabled, this will issue a warning if a pattern match contains too many guards (over 20 at the diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 6d02391c16..6ea2ef65df 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -6035,12 +6035,13 @@ declaration doesn't matter, it can be replaced with an underscore -- Equivalent to data instance F Int b = Int -When the flag :ghc-flag:`-fwarn-unused-matches` is enabled, type variables that are -mentioned in the patterns on the left hand side, but not used on the right -hand side are reported. Variables that occur multiple times on the left hand side -are also considered used. To suppress the warnings, unused variables should -be either replaced or prefixed with underscores. Type variables starting with -an underscore (``_x``) are otherwise treated as ordinary type variables. +When the flag :ghc-flag:`-Wunused-type-patterns` is enabled, type +variables that are mentioned in the patterns on the left hand side, but not +used on the right hand side are reported. Variables that occur multiple times +on the left hand side are also considered used. To suppress the warnings, +unused variables should be either replaced or prefixed with underscores. Type +variables starting with an underscore (``_x``) are otherwise treated as +ordinary type variables. This resembles the wildcards that can be used in :ref:`partial-type-signatures`. However, there are some differences. @@ -6193,9 +6194,10 @@ for data instances. For example, the ``[e]`` instance for ``Elem`` is :: Type arguments can be replaced with underscores (``_``) if the names of the arguments don't matter. This is the same as writing type variables -with unique names. Unused type arguments should be replaced or prefixed -with underscores to avoid warnings when the `-fwarn-unused-matches` flag -is enabled. The same rules apply as for :ref:`data-instance-declarations`. +with unique names. Unused type arguments can be replaced or prefixed +with underscores to avoid warnings when the +:ghc-flag:`-Wunused-type-patterns` flag is enabled. The same rules apply +as for :ref:`data-instance-declarations`. Type family instance declarations are only legitimate when an appropriate family declaration is in scope - just like class instances @@ -7701,6 +7703,14 @@ The two are treated identically. Of course ``forall`` becomes a keyword; you can't use ``forall`` as a type variable any more! +If the :ghc-flag:`-Wunused-foralls` flag is enabled, a warning will be emitted +when you write a type variable in an explicit ``forall`` statement that is +otherwise unused. For instance: :: + + g :: forall a b. (b -> b) + +would warn about the unused type variable `a`. + .. _flexible-contexts: The context of a type signature diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index e4f8d2c3a7..afcee5b5d7 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -44,6 +44,7 @@ The following flags are simple ways to select standard "packages" of warnings: * :ghc-flag:`-Wunused-binds` * :ghc-flag:`-Wunused-matches` + * :ghc-flag:`-Wunused-foralls` * :ghc-flag:`-Wunused-imports` * :ghc-flag:`-Wincomplete-patterns` * :ghc-flag:`-Wdodgy-exports` @@ -871,14 +872,18 @@ of ``-W(no-)*``. single: unused matches, warning single: matches, unused - Report all unused variables which arise from pattern matches, - including patterns consisting of a single variable. This includes - unused type variables in type family instances. For instance + Report all unused variables which arise from term-level pattern matches, + including patterns consisting of a single variable. For instance ``f x y = []`` would report ``x`` and ``y`` as unused. The warning is suppressed if the variable name begins with an underscore, thus: :: f _x = True + Note that :ghc-flag:`-Wunused-matches` does not warn about variables which + arise from type-level patterns, as found in type family and data family + instances. This must be enabled separately through the + :ghc-flag:`-Wunused-type-patterns` flag. + .. ghc-flag:: -Wunused-do-bind .. index:: @@ -900,6 +905,41 @@ of ``-W(no-)*``. do { mapM_ popInt xs ; return 10 } +.. ghc-flag:: -Wunused-type-patterns + + .. index:: + single: unused type patterns, warning + single: type patterns, unused + + Report all unused type variables which arise from patterns in type family + and data family instances. For instance: :: + + type instance F x y = [] + + would report ``x`` and ``y`` as unused. The warning is suppressed if the + type variable name begins with an underscore, like so: :: + + type instance F _x _y = [] + + Unlike :ghc-flag:`-Wunused-matches`, :ghc-flag:`-Wunused-type-variables` is + not implied by :ghc-flag:`-Wall`. The rationale for this decision is that + unlike term-level pattern names, type names are often chosen expressly for + documentation purposes, so using underscores in type names can make the + documentation harder to read. + +.. ghc-flag:: -Wunused-foralls + + .. index:: + single: unused foralls, warning + single: foralls, unused + + Report all unused type variables which arise from explicit, user-written + ``forall`` statements. For instance: :: + + g :: forall a b c. (b -> b) + + would report ``a`` and ``c`` as unused. + .. ghc-flag:: -Wwrong-do-bind .. index:: diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index 26cd7aa7fd..db340923e1 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -8,7 +8,7 @@ -- Module : Data.Either -- Copyright : (c) The University of Glasgow 2001 -- License : BSD-style (see the file libraries/base/LICENSE) --- +-- -- Maintainer : libraries@haskell.org -- Stability : experimental -- Portability : portable @@ -281,7 +281,7 @@ isRight (Right _) = True type family EqEither a b where EqEither ('Left x) ('Left y) = x == y EqEither ('Right x) ('Right y) = x == y - EqEither _a _b = 'False + EqEither a b = 'False type instance a == b = EqEither a b {- diff --git a/libraries/base/Data/Type/Bool.hs b/libraries/base/Data/Type/Bool.hs index acac3eb592..cfd4bfada6 100644 --- a/libraries/base/Data/Type/Bool.hs +++ b/libraries/base/Data/Type/Bool.hs @@ -28,14 +28,14 @@ import Data.Bool -- | Type-level "If". @If True a b@ ==> @a@; @If False a b@ ==> @b@ type family If cond tru fls where - If 'True tru _fls = tru - If 'False _tru fls = fls + If 'True tru fls = tru + If 'False tru fls = fls -- | Type-level "and" type family a && b where - 'False && _a = 'False + 'False && a = 'False 'True && a = a - _a && 'False = 'False + a && 'False = 'False a && 'True = a a && a = a infixr 3 && @@ -43,9 +43,9 @@ infixr 3 && -- | Type-level "or" type family a || b where 'False || a = a - 'True || _a = 'True + 'True || a = 'True a || 'False = a - _a || 'True = 'True + a || 'True = 'True a || a = a infixr 2 || diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index a72e268a71..75d2a6ca7e 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -205,37 +205,37 @@ families. -- all of the following closed type families are local to this module type family EqStar (a :: *) (b :: *) where - EqStar _a _a = 'True - EqStar _a _b = 'False + EqStar a a = 'True + EqStar a b = 'False -- This looks dangerous, but it isn't. This allows == to be defined -- over arbitrary type constructors. type family EqArrow (a :: k1 -> k2) (b :: k1 -> k2) where - EqArrow _a _a = 'True - EqArrow _a _b = 'False + EqArrow a a = 'True + EqArrow a b = 'False type family EqBool a b where EqBool 'True 'True = 'True EqBool 'False 'False = 'True - EqBool _a _b = 'False + EqBool a b = 'False type family EqOrdering a b where EqOrdering 'LT 'LT = 'True EqOrdering 'EQ 'EQ = 'True EqOrdering 'GT 'GT = 'True - EqOrdering _a _b = 'False + EqOrdering a b = 'False type EqUnit (a :: ()) (b :: ()) = 'True type family EqList a b where EqList '[] '[] = 'True EqList (h1 ': t1) (h2 ': t2) = (h1 == h2) && (t1 == t2) - EqList _a _b = 'False + EqList a b = 'False type family EqMaybe a b where EqMaybe 'Nothing 'Nothing = 'True EqMaybe ('Just x) ('Just y) = x == y - EqMaybe _a _b = 'False + EqMaybe a b = 'False type family Eq2 a b where Eq2 '(a1, b1) '(a2, b2) = a1 == a2 && b1 == b2 diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index 3ac4d5c500..4cadf437e5 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -763,27 +763,27 @@ newtype (:.:) f (g :: * -> *) (p :: *) = Comp1 { unComp1 :: f (g p) } data family URec (a :: *) (p :: *) -- | Used for marking occurrences of 'Addr#' -data instance URec (Ptr ()) _p = UAddr { uAddr# :: Addr# } +data instance URec (Ptr ()) p = UAddr { uAddr# :: Addr# } deriving (Eq, Ord, Generic) -- | Used for marking occurrences of 'Char#' -data instance URec Char _p = UChar { uChar# :: Char# } +data instance URec Char p = UChar { uChar# :: Char# } deriving (Eq, Ord, Show, Generic) -- | Used for marking occurrences of 'Double#' -data instance URec Double _p = UDouble { uDouble# :: Double# } +data instance URec Double p = UDouble { uDouble# :: Double# } deriving (Eq, Ord, Show, Generic) -- | Used for marking occurrences of 'Float#' -data instance URec Float _p = UFloat { uFloat# :: Float# } +data instance URec Float p = UFloat { uFloat# :: Float# } deriving (Eq, Ord, Show, Generic) -- | Used for marking occurrences of 'Int#' -data instance URec Int _p = UInt { uInt# :: Int# } +data instance URec Int p = UInt { uInt# :: Int# } deriving (Eq, Ord, Show, Generic) -- | Used for marking occurrences of 'Word#' -data instance URec Word _p = UWord { uWord# :: Word# } +data instance URec Word p = UWord { uWord# :: Word# } deriving (Eq, Ord, Show, Generic) -- | Type synonym for 'URec': 'Addr#' @@ -1051,7 +1051,7 @@ class (kparam ~ 'KProxy) => SingKind (kparam :: KProxy k) where fromSing :: Sing (a :: k) -> DemoteRep kparam -- Singleton symbols -data instance Sing (_s :: Symbol) where +data instance Sing (s :: Symbol) where SSym :: KnownSymbol s => Sing s instance KnownSymbol a => SingI a where sing = SSym @@ -1061,7 +1061,7 @@ instance SingKind ('KProxy :: KProxy Symbol) where fromSing (SSym :: Sing s) = symbolVal (Proxy :: Proxy s) -- Singleton booleans -data instance Sing (_a :: Bool) where +data instance Sing (a :: Bool) where STrue :: Sing 'True SFalse :: Sing 'False @@ -1074,7 +1074,7 @@ instance SingKind ('KProxy :: KProxy Bool) where fromSing SFalse = False -- Singleton Maybe -data instance Sing (_b :: Maybe _a) where +data instance Sing (b :: Maybe a) where SNothing :: Sing 'Nothing SJust :: Sing a -> Sing ('Just a) @@ -1089,7 +1089,7 @@ instance SingKind ('KProxy :: KProxy a) => fromSing (SJust a) = Just (fromSing a) -- Singleton Fixity -data instance Sing (_a :: FixityI) where +data instance Sing (a :: FixityI) where SPrefix :: Sing 'PrefixI SInfix :: Sing a -> Integer -> Sing ('InfixI a n) @@ -1103,7 +1103,7 @@ instance SingKind ('KProxy :: KProxy FixityI) where fromSing (SInfix a n) = Infix (fromSing a) (I# (integerToInt n)) -- Singleton Associativity -data instance Sing (_a :: Associativity) where +data instance Sing (a :: Associativity) where SLeftAssociative :: Sing 'LeftAssociative SRightAssociative :: Sing 'RightAssociative SNotAssociative :: Sing 'NotAssociative @@ -1119,7 +1119,7 @@ instance SingKind ('KProxy :: KProxy Associativity) where fromSing SNotAssociative = NotAssociative -- Singleton SourceUnpackedness -data instance Sing (_a :: SourceUnpackedness) where +data instance Sing (a :: SourceUnpackedness) where SNoSourceUnpackedness :: Sing 'NoSourceUnpackedness SSourceNoUnpack :: Sing 'SourceNoUnpack SSourceUnpack :: Sing 'SourceUnpack @@ -1135,7 +1135,7 @@ instance SingKind ('KProxy :: KProxy SourceUnpackedness) where fromSing SSourceUnpack = SourceUnpack -- Singleton SourceStrictness -data instance Sing (_a :: SourceStrictness) where +data instance Sing (a :: SourceStrictness) where SNoSourceStrictness :: Sing 'NoSourceStrictness SSourceLazy :: Sing 'SourceLazy SSourceStrict :: Sing 'SourceStrict @@ -1151,7 +1151,7 @@ instance SingKind ('KProxy :: KProxy SourceStrictness) where fromSing SSourceStrict = SourceStrict -- Singleton DecidedStrictness -data instance Sing (_a :: DecidedStrictness) where +data instance Sing (a :: DecidedStrictness) where SDecidedLazy :: Sing 'DecidedLazy SDecidedStrict :: Sing 'DecidedStrict SDecidedUnpack :: Sing 'DecidedUnpack diff --git a/libraries/base/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs index b32721d63c..a51ba910e0 100644 --- a/libraries/base/GHC/TypeLits.hs +++ b/libraries/base/GHC/TypeLits.hs @@ -146,13 +146,13 @@ instance Read SomeSymbol where readsPrec p xs = [ (someSymbolVal a, ys) | (a,ys) <- readsPrec p xs ] type family EqNat (a :: Nat) (b :: Nat) where - EqNat _a _a = 'True - EqNat _a _b = 'False + EqNat a a = 'True + EqNat a b = 'False type instance a == b = EqNat a b type family EqSymbol (a :: Symbol) (b :: Symbol) where - EqSymbol _a _a = 'True - EqSymbol _a _b = 'False + EqSymbol a a = 'True + EqSymbol a b = 'False type instance a == b = EqSymbol a b -------------------------------------------------------------------------------- diff --git a/testsuite/tests/determinism/should_compile/determ004.hs b/testsuite/tests/determinism/should_compile/determ004.hs index 88fe88a770..c74f8d02d8 100644 --- a/testsuite/tests/determinism/should_compile/determ004.hs +++ b/testsuite/tests/determinism/should_compile/determ004.hs @@ -225,7 +225,7 @@ data TyFun (a :: *) (b :: *) type family Apply (f :: TyFun k1 k2 -> *) (x :: k1) :: k2 -data instance Sing (f :: TyFun _k1 _k2 -> *) = +data instance Sing (f :: TyFun k1 k2 -> *) = SLambda { applySing :: forall t. Sing t -> Sing (Apply f t) } type SingFunction1 f = forall t. Sing t -> Sing (Apply f t) @@ -273,9 +273,9 @@ type family Foldr1 (a_afe5 :: TyFun a_afdP (TyFun a_afdP a_afdP -> *) -> *) (a_afe6 :: [a_afdP]) :: a_afdP where - Foldr1 _z_afe7 '[x_afe8] = x_afe8 + Foldr1 z_afe7 '[x_afe8] = x_afe8 Foldr1 f_afe9 ((:) x_afea ((:) wild_1627448474_afeb wild_1627448476_afec)) = Apply (Apply f_afe9 x_afea) (Apply (Apply Foldr1Sym0 f_afe9) (Let1627448493XsSym4 f_afe9 x_afea wild_1627448474_afeb wild_1627448476_afec)) - Foldr1 _z_afew '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" + Foldr1 z_afew '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" sFoldr1 :: forall (x :: TyFun a_afdP (TyFun a_afdP a_afdP -> *) -> *) diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 28ea8bd624..9fece9c1c4 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -268,8 +268,8 @@ test('T10931', normal, compile, ['']) test('T11187', normal, compile, ['']) test('T11067', normal, compile, ['']) test('T10318', normal, compile, ['']) -test('UnusedTyVarWarnings', normal, compile, ['-W']) -test('UnusedTyVarWarningsNamedWCs', normal, compile, ['-W']) +test('UnusedTyVarWarnings', normal, compile, ['-Wunused-type-patterns']) +test('UnusedTyVarWarningsNamedWCs', normal, compile, ['-Wunused-type-patterns']) test('T11408', normal, compile, ['']) test('T11361', normal, compile, ['']) test('T11361a', normal, compile_fail, ['']) diff --git a/testsuite/tests/simplCore/should_compile/T10689a.hs b/testsuite/tests/simplCore/should_compile/T10689a.hs index 477d80cb14..5b21b42db7 100644 --- a/testsuite/tests/simplCore/should_compile/T10689a.hs +++ b/testsuite/tests/simplCore/should_compile/T10689a.hs @@ -76,9 +76,9 @@ type family Foldr1 (a_afe5 :: TyFun a_afdP (TyFun a_afdP a_afdP -> *) -> *) (a_afe6 :: [a_afdP]) :: a_afdP where - Foldr1 _z_afe7 '[x_afe8] = x_afe8 + Foldr1 z_afe7 '[x_afe8] = x_afe8 Foldr1 f_afe9 ((:) x_afea ((:) wild_1627448474_afeb wild_1627448476_afec)) = Apply (Apply f_afe9 x_afea) (Apply (Apply Foldr1Sym0 f_afe9) (Let1627448493XsSym4 f_afe9 x_afea wild_1627448474_afeb wild_1627448476_afec)) - Foldr1 _z_afew '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" + Foldr1 z_afew '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" sFoldr1 :: forall (x :: TyFun a_afdP (TyFun a_afdP a_afdP -> *) -> *) diff --git a/utils/mkUserGuidePart/Options/Warnings.hs b/utils/mkUserGuidePart/Options/Warnings.hs index 256d01f9fa..3fa9bf087e 100644 --- a/utils/mkUserGuidePart/Options/Warnings.hs +++ b/utils/mkUserGuidePart/Options/Warnings.hs @@ -291,6 +291,18 @@ warningsOptions = , flagType = DynamicFlag , flagReverse = "-Wno-unused-matches" } + , flag { flagName = "-Wunused-foralls" + , flagDescription = "warn about type variables in user-written "++ + "``forall``\\s that are unused" + , flagType = DynamicFlag + , flagReverse = "-Wno-unused-foralls" + } + , flag { flagName = "-Wunused-type-variables" + , flagDescription = "warn about variables in type family or data "++ + "family instances that are unused" + , flagType = DynamicFlag + , flagReverse = "-Wno-unused-type-variables" + } , flag { flagName = "-Wunused-do-bind" , flagDescription = "warn about do bindings that appear to throw away values of types "++ |