From 275836d211d119cb8786a91ca3108a4daa693cb2 Mon Sep 17 00:00:00 2001 From: Torsten Schmits <git@tryp.io> Date: Wed, 26 Apr 2023 21:56:16 +0200 Subject: [PATCH] Add structured error messages for GHC.Rename.Utils Tracking ticket: #20115 MR: !10350 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. --- compiler/GHC/Rename/Bind.hs | 11 +- compiler/GHC/Rename/Expr.hs | 3 +- compiler/GHC/Rename/HsType.hs | 6 +- compiler/GHC/Rename/Module.hs | 29 +-- compiler/GHC/Rename/Utils.hs | 213 +++++------------- compiler/GHC/Tc/Errors/Ppr.hs | 173 +++++++++++++- compiler/GHC/Tc/Errors/Types.hs | 155 ++++++++++++- compiler/GHC/Tc/Module.hs | 2 +- compiler/GHC/Types/Error/Codes.hs | 12 + compiler/GHC/Types/Hint.hs | 5 + compiler/GHC/Types/Hint/Ppr.hs | 2 + .../tests/deSugar/should_compile/ds053.stderr | 2 +- .../deriving/should_compile/T13919.stderr | 2 +- testsuite/tests/driver/t22391/t22391.stderr | 2 +- testsuite/tests/driver/t22391/t22391j.stderr | 2 +- testsuite/tests/driver/werror.stderr | 4 +- testsuite/tests/gadt/T12087.stderr | 10 +- testsuite/tests/gadt/T14320.stderr | 2 +- testsuite/tests/gadt/T16427.stderr | 2 +- testsuite/tests/gadt/T18191.stderr | 10 +- testsuite/tests/ghci/prog018/prog018.stdout | 2 +- .../should_compile/ExplicitForAllFams2.stderr | 8 +- .../should_compile/T16356_Compile2.stderr | 12 +- .../should_compile/T16632.stderr | 2 +- .../should_compile/UnusedTyVarWarnings.stderr | 8 +- .../UnusedTyVarWarningsNamedWCs.stderr | 8 +- .../should_fail/SimpleFail6.stderr | 2 +- .../should_fail/T16110_Fail1.stderr | 2 +- .../tests/mdo/should_fail/mdofail002.stderr | 2 +- .../tests/mdo/should_fail/mdofail003.stderr | 2 +- testsuite/tests/module/mod110.stderr | 2 +- testsuite/tests/module/mod151.stderr | 2 +- testsuite/tests/module/mod152.stderr | 2 +- testsuite/tests/module/mod153.stderr | 2 +- testsuite/tests/module/mod164.stderr | 2 +- testsuite/tests/module/mod165.stderr | 2 +- testsuite/tests/module/mod23.stderr | 2 +- testsuite/tests/module/mod24.stderr | 2 +- testsuite/tests/module/mod62.stderr | 2 +- .../overloadedrecflds/ghci/GHCiDRF.stdout | 6 +- .../ghci/duplicaterecfldsghci01.stdout | 2 +- .../should_compile/BootFldReexport.stderr | 2 +- .../should_fail/DRFUnused.stderr | 2 +- .../should_fail/NoFieldSelectorsFail.stderr | 2 +- .../T11167_ambiguous_fixity.stderr | 2 +- .../T13132_duplicaterecflds.stderr | 4 +- .../should_fail/T16745.stderr | 2 +- .../should_fail/T17420.stderr | 2 +- .../should_fail/T17469.stderr | 2 +- .../T18999_NoDisambiguateRecordFields.stderr | 2 +- .../should_fail/T23010_fail.stderr | 2 +- .../overloadedrecfldsfail02.stderr | 2 +- .../overloadedrecfldsfail04.stderr | 2 +- .../overloadedrecfldsfail05.stderr | 2 +- .../overloadedrecfldsfail06.stderr | 6 +- .../overloadedrecfldsfail11.stderr | 2 +- .../overloadedrecfldsfail12.stderr | 4 +- .../overloadedrecfldsfail13.stderr | 8 +- .../overloadedrecfldswasrunnowfail06.stderr | 8 +- .../parser/should_compile/read014.stderr | 4 +- .../tests/parser/should_fail/T12446.stderr | 4 +- .../tests/parser/should_fail/T18251c.stderr | 4 +- .../tests/patsyn/should_fail/T14114.stderr | 6 +- testsuite/tests/polykinds/T10451.stderr | 2 +- .../tests/quasiquotation/qq006/qq006.stderr | 2 +- .../tests/rename/should_compile/T13839.stdout | 2 +- .../rename/should_compile/T13839a.stderr | 2 +- .../tests/rename/should_compile/T17a.stderr | 2 +- .../tests/rename/should_compile/T17b.stderr | 2 +- .../tests/rename/should_compile/T17d.stderr | 2 +- .../tests/rename/should_compile/T17e.stderr | 4 +- .../tests/rename/should_compile/T1972.stderr | 2 +- .../tests/rename/should_compile/T3371.stderr | 2 +- .../tests/rename/should_compile/T3449.stderr | 2 +- .../tests/rename/should_compile/T7145b.stderr | 2 +- .../tests/rename/should_compile/mc10.stderr | 2 +- .../tests/rename/should_compile/rn040.stderr | 4 +- .../tests/rename/should_compile/rn041.stderr | 6 +- .../tests/rename/should_compile/rn047.stderr | 2 +- .../tests/rename/should_compile/rn063.stderr | 4 +- .../should_compile/unused_haddock.stderr | 2 +- .../rename/should_fail/T11167_ambig.stderr | 4 +- .../tests/rename/should_fail/T13644.stderr | 2 +- .../tests/rename/should_fail/T13847.stderr | 2 +- .../tests/rename/should_fail/T15487.stderr | 2 +- .../rename/should_fail/T15957_Fail.stderr | 36 +-- .../tests/rename/should_fail/T16114.stderr | 2 +- .../tests/rename/should_fail/T18240a.stderr | 10 +- .../tests/rename/should_fail/T18240b.stderr | 12 +- .../tests/rename/should_fail/T5951.stderr | 2 +- .../tests/rename/should_fail/T6148a.stderr | 2 +- .../tests/rename/should_fail/T6148b.stderr | 2 +- .../tests/rename/should_fail/T6148c.stderr | 2 +- .../tests/rename/should_fail/T6148d.stderr | 8 +- .../tests/rename/should_fail/T8448.stderr | 3 +- .../tests/rename/should_fail/rnfail001.stderr | 2 +- .../tests/rename/should_fail/rnfail004.stderr | 4 +- .../tests/rename/should_fail/rnfail021.stderr | 2 +- .../tests/rename/should_fail/rnfail034.stderr | 2 +- .../tests/rename/should_fail/rnfail039.stderr | 2 +- .../tests/rename/should_fail/rnfail044.stderr | 2 +- .../tests/rename/should_fail/rnfail046.stderr | 2 +- testsuite/tests/runghc/T17171b.stderr | 2 +- testsuite/tests/th/T12411.stderr | 4 +- testsuite/tests/th/T16133.stderr | 8 +- testsuite/tests/th/TH_recover_warns.stderr | 4 +- testsuite/tests/th/TH_spliceD1.stderr | 2 +- .../typecheck/should_compile/T18470.stderr | 2 +- .../typecheck/should_compile/T2497.stderr | 2 +- .../should_fail/ExplicitSpecificity5.stderr | 2 +- .../should_fail/ExplicitSpecificity6.stderr | 4 +- .../should_fail/ExplicitSpecificity9.stderr | 2 +- .../tests/typecheck/should_fail/T15527.stderr | 4 +- .../tests/typecheck/should_fail/T16394.stderr | 2 +- .../tests/typecheck/should_fail/T18455.stderr | 2 +- .../typecheck/should_fail/T18723a.stderr | 2 +- .../typecheck/should_fail/T18723b.stderr | 2 +- .../typecheck/should_fail/T18723c.stderr | 2 +- .../typecheck/should_fail/T19397E1.stderr | 2 +- .../typecheck/should_fail/T19397E2.stderr | 2 +- .../tests/typecheck/should_fail/T8570.stderr | 2 +- .../typecheck/should_fail/tcfail037.stderr | 2 +- .../typecheck/should_fail/tcfail038.stderr | 4 +- .../typecheck/should_fail/tcfail083.stderr | 2 +- .../typecheck/should_fail/tcfail084.stderr | 2 +- .../warnings/should_fail/WarningGroups.stderr | 4 +- 126 files changed, 622 insertions(+), 390 deletions(-) diff --git a/compiler/GHC/Rename/Bind.hs b/compiler/GHC/Rename/Bind.hs index 661c271fb97e..503e56bd57e9 100644 --- a/compiler/GHC/Rename/Bind.hs +++ b/compiler/GHC/Rename/Bind.hs @@ -42,7 +42,7 @@ import GHC.Rename.Names import GHC.Rename.Env import GHC.Rename.Fixity import GHC.Rename.Utils ( mapFvRn - , checkDupRdrNames, checkDupRdrNamesN + , checkDupRdrNames , warnUnusedLocalBinds , warnForallIdentifier , checkUnusedRecordWildcard @@ -719,7 +719,7 @@ rnPatSynBind sig_fn bind@(PSB { psb_id = L l name -- from the left-hand side case details of PrefixCon _ vars -> - do { checkDupRdrNamesN vars + do { checkDupRdrNames vars ; names <- mapM lookupPatSynBndr vars ; return ( (pat', PrefixCon noTypeArgs names) , mkFVs (map unLoc names)) } @@ -877,7 +877,7 @@ rnMethodBinds :: Bool -- True <=> is a class declaration -- * the default method bindings in a class decl -- * the method bindings in an instance decl rnMethodBinds is_cls_decl cls ktv_names binds sigs - = do { checkDupRdrNamesN (collectMethodBinders binds) + = do { checkDupRdrNames (collectMethodBinders binds) -- Check that the same method is not given twice in the -- same instance decl instance C T where -- f x = ... @@ -1038,18 +1038,17 @@ renameSig ctxt sig@(ClassOpSig _ is_deflt vs ty) <+> quotes (ppr v1)) renameSig _ (SpecInstSig (_, src) ty) - = do { checkInferredVars doc inf_msg ty + = do { checkInferredVars doc ty ; (new_ty, fvs) <- rnHsSigType doc TypeLevel ty -- Check if there are any nested `forall`s or contexts, which are -- illegal in the type of an instance declaration (see -- Note [No nested foralls or contexts in instance types] in -- GHC.Hs.Type). - ; addNoNestedForallsContextsErr doc (text "SPECIALISE instance type") + ; addNoNestedForallsContextsErr doc NFC_Specialize (getLHsInstDeclHead new_ty) ; return (SpecInstSig (noAnn, src) new_ty,fvs) } where doc = SpecInstSigCtx - inf_msg = Just (text "Inferred type variables are not allowed") -- {-# SPECIALISE #-} pragmas can refer to imported Ids -- so, in the top-level case (when mb_names is Nothing) diff --git a/compiler/GHC/Rename/Expr.hs b/compiler/GHC/Rename/Expr.hs index b68ff6a49215..2afc0f0fa604 100644 --- a/compiler/GHC/Rename/Expr.hs +++ b/compiler/GHC/Rename/Expr.hs @@ -56,6 +56,7 @@ import GHC.Driver.Session import GHC.Builtin.Names import GHC.Builtin.Types ( nilDataConName ) +import GHC.Types.Basic (TypeOrKind (TypeLevel)) import GHC.Types.FieldLabel import GHC.Types.Fixity import GHC.Types.Id.Make @@ -324,7 +325,7 @@ rnExpr (HsApp x fun arg) rnExpr (HsAppType _ fun at arg) = do { type_app <- xoptM LangExt.TypeApplications - ; unless type_app $ addErr $ typeAppErr "type" $ hswc_body arg + ; unless type_app $ addErr $ typeAppErr TypeLevel $ hswc_body arg ; (fun',fvFun) <- rnLExpr fun ; (arg',fvArg) <- rnHsWcType HsTypeCtx arg ; return (HsAppType NoExtField fun' at arg', fvFun `plusFV` fvArg) } diff --git a/compiler/GHC/Rename/HsType.hs b/compiler/GHC/Rename/HsType.hs index 500a6f840770..049bbe2c2207 100644 --- a/compiler/GHC/Rename/HsType.hs +++ b/compiler/GHC/Rename/HsType.hs @@ -49,7 +49,7 @@ import GHC.Hs import GHC.Rename.Env import GHC.Rename.Doc import GHC.Rename.Utils ( mapFvRn, bindLocalNamesFV - , typeAppErr, newLocalBndrRn, checkDupRdrNamesN + , typeAppErr, newLocalBndrRn, checkDupRdrNames , checkShadowedRdrNames, warnForallIdentifier ) import GHC.Rename.Fixity ( lookupFieldFixityRn, lookupFixityRn , lookupTyFixityRn ) @@ -686,7 +686,7 @@ rnHsTyKi env (HsAppTy _ ty1 ty2) rnHsTyKi env (HsAppKindTy _ ty at k) = do { kind_app <- xoptM LangExt.TypeApplications - ; unless kind_app (addErr (typeAppErr "kind" k)) + ; unless kind_app (addErr (typeAppErr KindLevel k)) ; (ty', fvs1) <- rnLHsTyKi env ty ; (k', fvs2) <- rnLHsTyKi (env {rtke_level = KindLevel }) k ; return (HsAppKindTy noExtField ty' at k', fvs1 `plusFV` fvs2) } @@ -1184,7 +1184,7 @@ bindLHsTyVarBndrs :: (OutputableBndrFlag flag 'Renamed) -> RnM (b, FreeVars) bindLHsTyVarBndrs doc wuf mb_assoc tv_bndrs thing_inside = do { when (isNothing mb_assoc) (checkShadowedRdrNames tv_names_w_loc) - ; checkDupRdrNamesN tv_names_w_loc + ; checkDupRdrNames tv_names_w_loc ; go tv_bndrs thing_inside } where tv_names_w_loc = map hsLTyVarLocName tv_bndrs diff --git a/compiler/GHC/Rename/Module.hs b/compiler/GHC/Rename/Module.hs index 1602b2b92df4..e91749cf2d26 100644 --- a/compiler/GHC/Rename/Module.hs +++ b/compiler/GHC/Rename/Module.hs @@ -30,7 +30,7 @@ import GHC.Rename.Bind import GHC.Rename.Doc import GHC.Rename.Env import GHC.Rename.Utils ( mapFvRn, bindLocalNames - , checkDupRdrNamesN, bindLocalNamesFV + , checkDupRdrNames, bindLocalNamesFV , checkShadowedRdrNames, warnUnusedTypePatterns , newLocalBndrsRn , noNestedForallsContextsErr @@ -605,7 +605,7 @@ rnClsInstDecl (ClsInstDecl { cid_poly_ty = inst_ty, cid_binds = mbinds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = oflag , cid_datafam_insts = adts }) - = do { checkInferredVars ctxt inf_err inst_ty + = do { checkInferredVars ctxt inst_ty ; (inst_ty', inst_fvs) <- rnHsSigType ctxt TypeLevel inst_ty ; let (ktv_names, _, head_ty') = splitLHsInstDeclTy inst_ty' -- Check if there are any nested `forall`s or contexts, which are @@ -613,7 +613,7 @@ rnClsInstDecl (ClsInstDecl { cid_poly_ty = inst_ty, cid_binds = mbinds -- Note [No nested foralls or contexts in instance types] in -- GHC.Hs.Type)... mb_nested_msg = noNestedForallsContextsErr - (text "Instance head") head_ty' + NFC_InstanceHead head_ty' -- ...then check if the instance head is actually headed by a -- class type constructor... eith_cls = case hsTyGetAppHead_maybe head_ty' of @@ -669,7 +669,6 @@ rnClsInstDecl (ClsInstDecl { cid_poly_ty = inst_ty, cid_binds = mbinds -- to remove the context). where ctxt = GenericCtx $ text "an instance declaration" - inf_err = Just (text "Inferred type variables are not allowed") -- The instance is malformed. We'd still like to make *some* progress -- (rather than failing outright), so we report an error and continue for @@ -1177,20 +1176,19 @@ rnSrcDerivDecl :: DerivDecl GhcPs -> RnM (DerivDecl GhcRn, FreeVars) rnSrcDerivDecl (DerivDecl _ ty mds overlap) = do { standalone_deriv_ok <- xoptM LangExt.StandaloneDeriving ; unless standalone_deriv_ok (addErr TcRnUnexpectedStandaloneDerivingDecl) - ; checkInferredVars ctxt inf_err nowc_ty + ; checkInferredVars ctxt nowc_ty ; (mds', ty', fvs) <- rnLDerivStrategy ctxt mds $ rnHsSigWcType ctxt ty -- Check if there are any nested `forall`s or contexts, which are -- illegal in the type of an instance declaration (see -- Note [No nested foralls or contexts in instance types] in -- GHC.Hs.Type). ; addNoNestedForallsContextsErr ctxt - (text "Standalone-derived instance head") + NFC_StandaloneDerivedInstanceHead (getLHsInstDeclHead $ dropWildCards ty') ; warnNoDerivStrat mds' loc ; return (DerivDecl noAnn ty' mds' overlap, fvs) } where ctxt = DerivDeclCtx - inf_err = Just (text "Inferred type variables are not allowed") loc = getLocA nowc_ty nowc_ty = dropWildCards ty @@ -1219,7 +1217,7 @@ rnHsRuleDecl (HsRule { rd_ext = (_, st) , rd_rhs = rhs }) = do { let rdr_names_w_loc = map (get_var . unLoc) tmvs ; mapM_ warnForallIdentifier rdr_names_w_loc - ; checkDupRdrNamesN rdr_names_w_loc + ; checkDupRdrNames rdr_names_w_loc ; checkShadowedRdrNames rdr_names_w_loc ; names <- newLocalBndrsRn rdr_names_w_loc ; let doc = RuleCtx (unLoc rule_name) @@ -1819,7 +1817,7 @@ rnTyClDecl (ClassDecl { tcdLayout = layout, ; let sig_rdr_names_w_locs = [op | L _ (ClassOpSig _ False ops _) <- sigs , op <- ops] - ; checkDupRdrNamesN sig_rdr_names_w_locs + ; checkDupRdrNames sig_rdr_names_w_locs -- Typechecker is responsible for checking that we only -- give default-method bindings for things in this class. -- The renamer *could* check this for class decls, but can't @@ -2191,14 +2189,13 @@ rnLHsDerivingClause doc rn_clause_pred :: LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars) rn_clause_pred pred_ty = do - let inf_err = Just (text "Inferred type variables are not allowed") - checkInferredVars doc inf_err pred_ty + checkInferredVars doc pred_ty ret@(pred_ty', _) <- rnHsSigType doc TypeLevel pred_ty -- Check if there are any nested `forall`s, which are illegal in a -- `deriving` clause. -- See Note [No nested foralls or contexts in instance types] -- (Wrinkle: Derived instances) in GHC.Hs.Type. - addNoNestedForallsContextsErr doc (text "Derived class type") + addNoNestedForallsContextsErr doc NFC_DerivedClassType (getLHsInstDeclHead pred_ty') pure ret @@ -2233,7 +2230,7 @@ rnLDerivStrategy doc mds thing_inside AnyclassStrategy _ -> boring_case (AnyclassStrategy noExtField) NewtypeStrategy _ -> boring_case (NewtypeStrategy noExtField) ViaStrategy (XViaStrategyPs _ via_ty) -> - do checkInferredVars doc inf_err via_ty + do checkInferredVars doc via_ty (via_ty', fvs1) <- rnHsSigType doc TypeLevel via_ty let HsSig { sig_bndrs = via_outer_bndrs , sig_body = via_body } = unLoc via_ty' @@ -2243,12 +2240,10 @@ rnLDerivStrategy doc mds thing_inside -- See Note [No nested foralls or contexts in instance types] -- (Wrinkle: Derived instances) in GHC.Hs.Type. addNoNestedForallsContextsErr doc - (quotes (text "via") <+> text "type") via_body + NFC_ViaType via_body (thing, fvs2) <- bindLocalNamesFV via_tvs thing_inside pure (ViaStrategy via_ty', thing, fvs1 `plusFV` fvs2) - inf_err = Just (text "Inferred type variables are not allowed") - boring_case :: ds -> RnM (ds, a, FreeVars) boring_case ds = do (thing, fvs) <- thing_inside @@ -2501,7 +2496,7 @@ rnConDecl (ConDeclGADT { con_names = names -- Note [GADT abstract syntax] (Wrinkle: No nested foralls or contexts) -- in GHC.Hs.Type. ; addNoNestedForallsContextsErr ctxt - (text "GADT constructor type signature") new_res_ty + NFC_GadtConSig new_res_ty ; let all_fvs = fvs1 `plusFV` fvs2 `plusFV` fvs3 diff --git a/compiler/GHC/Rename/Utils.hs b/compiler/GHC/Rename/Utils.hs index a00d97dd0dc4..7b631edac0d8 100644 --- a/compiler/GHC/Rename/Utils.hs +++ b/compiler/GHC/Rename/Utils.hs @@ -9,7 +9,7 @@ This module contains miscellaneous functions related to renaming. -} module GHC.Rename.Utils ( - checkDupRdrNames, checkDupRdrNamesN, checkShadowedRdrNames, + checkDupRdrNames, checkShadowedRdrNames, checkDupNames, checkDupAndShadowedNames, dupNamesErr, checkTupSize, checkCTupSize, addFvRn, mapFvRn, mapMaybeFvRn, @@ -44,7 +44,6 @@ import GHC.Types.Name.Reader import GHC.Tc.Errors.Types -- import GHC.Tc.Utils.Env import GHC.Tc.Utils.Monad -import GHC.Types.Error import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.Name.Env @@ -53,19 +52,16 @@ import GHC.Types.SrcLoc as SrcLoc import GHC.Types.SourceFile import GHC.Types.SourceText ( SourceText(..), IntegralLit ) import GHC.Utils.Outputable -import GHC.Utils.Panic import GHC.Utils.Misc -import GHC.Types.Basic ( TopLevelFlag(..), Origin(Generated) ) +import GHC.Types.Basic ( TopLevelFlag(..), Origin(Generated), TypeOrKind ) import GHC.Data.List.SetOps ( removeDupsOn ) import GHC.Data.Maybe ( whenIsJust ) import GHC.Driver.Session import GHC.Data.FastString import Control.Monad -import Data.List (find, sortBy) import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE ) import qualified Data.List.NonEmpty as NE import qualified GHC.LanguageExtensions as LangExt -import GHC.Data.Bag import qualified Data.List as List {- @@ -111,14 +107,7 @@ bindLocalNamesFV names enclosed_scope checkDupRdrNames :: [LocatedN RdrName] -> RnM () -- Check for duplicated names in a binding group checkDupRdrNames rdr_names_w_loc - = mapM_ (dupNamesErr getLocA) dups - where - (_, dups) = removeDupsOn unLoc rdr_names_w_loc - -checkDupRdrNamesN :: [LocatedN RdrName] -> RnM () --- Check for duplicated names in a binding group -checkDupRdrNamesN rdr_names_w_loc - = mapM_ (dupNamesErr getLocA) dups + = mapM_ (\ ns -> dupNamesErr (getLocA <$> ns) (unLoc <$> ns)) dups where (_, dups) = removeDupsOn unLoc rdr_names_w_loc @@ -129,7 +118,7 @@ checkDupNames names = check_dup_names (filterOut isSystemName names) check_dup_names :: [Name] -> RnM () check_dup_names names - = mapM_ (dupNamesErr nameSrcSpan) dups + = mapM_ (\ ns -> dupNamesErr (nameSrcSpan <$> ns) (getRdrName <$> ns)) dups where (_, dups) = removeDupsOn nameOccName names @@ -192,19 +181,15 @@ checkShadowedOccs (global_env,local_env) get_loc_occ ns -- @{a}@, but @forall a. [a] -> [a]@ would be accepted. -- See @Note [Unobservably inferred type variables]@. checkInferredVars :: HsDocContext - -> Maybe SDoc - -- ^ The error msg if the signature is not allowed to contain - -- manually written inferred variables. -> LHsSigType GhcPs -> RnM () -checkInferredVars _ Nothing _ = return () -checkInferredVars ctxt (Just msg) ty = +checkInferredVars ctxt ty = let bndrs = sig_ty_bndrs ty - in case find ((==) InferredSpec . hsTyVarBndrFlag) bndrs of - Nothing -> return () - Just _ -> addErr $ + in case filter ((==) InferredSpec . hsTyVarBndrFlag) bndrs of + [] -> return () + iv : ivs -> addErr $ TcRnWithHsDocContext ctxt $ - mkTcRnUnknownMessage $ mkPlainError noHints msg + TcRnIllegalInferredTyVars (iv NE.:| ivs) where sig_ty_bndrs :: LHsSigType GhcPs -> [HsTyVarBndr Specificity GhcPs] sig_ty_bndrs (L _ (HsSig{sig_bndrs = outer_bndrs})) @@ -287,7 +272,9 @@ Note [No nested foralls or contexts in instance types] in GHC.Hs.Type). -- "GHC.Rename.Module" and 'renameSig' in "GHC.Rename.Bind"). -- See @Note [No nested foralls or contexts in instance types]@ in -- "GHC.Hs.Type". -noNestedForallsContextsErr :: SDoc -> LHsType GhcRn -> Maybe (SrcSpan, TcRnMessage) +noNestedForallsContextsErr :: NestedForallsContextsIn + -> LHsType GhcRn + -> Maybe (SrcSpan, TcRnMessage) noNestedForallsContextsErr what lty = case ignoreParens lty of L l (HsForAllTy { hst_tele = tele }) @@ -304,12 +291,13 @@ noNestedForallsContextsErr what lty = _ -> Nothing where nested_foralls_contexts_err = - mkTcRnUnknownMessage $ mkPlainError noHints $ - what <+> text "cannot contain nested" - <+> quotes forAllLit <> text "s or contexts" + TcRnNestedForallsContexts what -- | A common way to invoke 'noNestedForallsContextsErr'. -addNoNestedForallsContextsErr :: HsDocContext -> SDoc -> LHsType GhcRn -> RnM () +addNoNestedForallsContextsErr :: HsDocContext + -> NestedForallsContextsIn + -> LHsType GhcRn + -> RnM () addNoNestedForallsContextsErr ctxt what lty = whenIsJust (noNestedForallsContextsErr what lty) $ \(l, err_msg) -> addErrAt l $ TcRnWithHsDocContext ctxt err_msg @@ -395,13 +383,7 @@ checkUnusedRecordWildcard loc fvs (Just dotdot_names) = -- -- The `..` here doesn't bind any variables as `x` is already bound. warnRedundantRecordWildcard :: RnM () -warnRedundantRecordWildcard = - whenWOptM Opt_WarnRedundantRecordWildcards $ - let msg = mkTcRnUnknownMessage $ - mkPlainDiagnostic (WarningWithFlag Opt_WarnRedundantRecordWildcards) - noHints - redundantWildcardWarning - in addDiagnostic msg +warnRedundantRecordWildcard = addDiagnostic TcRnRedundantRecordWildcard -- | Produce a warning when no variables bound by a `..` pattern are used. @@ -418,21 +400,19 @@ warnUnusedRecordWildcard :: [Name] -> FreeVars -> RnM () warnUnusedRecordWildcard ns used_names = do let used = filter (`elemNameSet` used_names) ns traceRn "warnUnused" (ppr ns $$ ppr used_names $$ ppr used) - warnIf (null used) - unusedRecordWildcardWarning + warnIf (null used) (TcRnUnusedRecordWildcard ns) warnUnusedLocalBinds, warnUnusedMatches, warnUnusedTypePatterns :: [Name] -> FreeVars -> RnM () -warnUnusedLocalBinds = check_unused Opt_WarnUnusedLocalBinds -warnUnusedMatches = check_unused Opt_WarnUnusedMatches -warnUnusedTypePatterns = check_unused Opt_WarnUnusedTypePatterns +warnUnusedLocalBinds = check_unused UnusedNameLocalBind +warnUnusedMatches = check_unused UnusedNameMatch +warnUnusedTypePatterns = check_unused UnusedNameTypePattern -check_unused :: WarningFlag -> [Name] -> FreeVars -> RnM () -check_unused flag bound_names used_names - = whenWOptM flag (warnUnused flag (filterOut (`elemNameSet` used_names) - bound_names)) +check_unused :: UnusedNameProv -> [Name] -> FreeVars -> RnM () +check_unused prov bound_names used_names + = warnUnused prov (filterOut (`elemNameSet` used_names) bound_names) warnForallIdentifier :: LocatedN RdrName -> RnM () warnForallIdentifier (L l rdr_name@(Unqual occ)) @@ -447,33 +427,30 @@ warnUnusedGREs :: [GlobalRdrElt] -> RnM () warnUnusedGREs gres = mapM_ warnUnusedGRE gres -- NB the Names must not be the names of record fields! -warnUnused :: WarningFlag -> [Name] -> RnM () -warnUnused flag names = - mapM_ (\ nm -> warnUnused1 flag nm (nameOccName nm)) names +warnUnused :: UnusedNameProv -> [Name] -> RnM () +warnUnused prov names = + mapM_ (\ nm -> warnUnused1 prov nm (nameOccName nm)) names -warnUnused1 :: WarningFlag -> Name -> OccName -> RnM () -warnUnused1 flag child child_occ +warnUnused1 :: UnusedNameProv -> Name -> OccName -> RnM () +warnUnused1 prov child child_occ = when (reportable child child_occ) $ - addUnusedWarning flag - child_occ (nameSrcSpan child) - (text $ "Defined but not used" ++ opt_str) - where - opt_str = case flag of - Opt_WarnUnusedTypePatterns -> " on the right hand side" - _ -> "" + warn_unused_name prov (nameSrcSpan child) child_occ + +warn_unused_name :: UnusedNameProv -> SrcSpan -> OccName -> RnM () +warn_unused_name prov span child_occ = + addDiagnosticAt span (TcRnUnusedName child_occ prov) warnUnusedGRE :: GlobalRdrElt -> RnM () warnUnusedGRE gre@(GRE { gre_lcl = lcl, gre_imp = is }) - | lcl = warnUnused1 Opt_WarnUnusedTopBinds nm occ + | lcl = warnUnused1 UnusedNameTopDecl nm occ | otherwise = when (reportable nm occ) (mapM_ warn is) where occ = greOccName gre nm = greName gre - warn spec = addUnusedWarning Opt_WarnUnusedTopBinds occ span msg - where - span = importSpecLoc spec - pp_mod = quotes (ppr (importSpecModule spec)) - msg = text "Imported from" <+> pp_mod <+> text "but not used" + warn spec = + warn_unused_name (UnusedNameImported (importSpecModule spec)) span occ + where + span = importSpecLoc spec -- | Should we report the fact that this 'Name' is unused? The -- 'OccName' may differ from 'nameOccName' due to @@ -487,29 +464,6 @@ reportable child child_occ | otherwise = not (startsWithUnderscore child_occ) -addUnusedWarning :: WarningFlag -> OccName -> SrcSpan -> SDoc -> RnM () -addUnusedWarning flag occ span msg = do - let diag = mkTcRnUnknownMessage $ mkPlainDiagnostic (WarningWithFlag flag) noHints $ - sep [msg <> colon, - nest 2 $ pprNonVarNameSpace (occNameSpace occ) - <+> quotes (ppr occ)] - addDiagnosticAt span diag - -unusedRecordWildcardWarning :: TcRnMessage -unusedRecordWildcardWarning = - mkTcRnUnknownMessage $ mkPlainDiagnostic (WarningWithFlag Opt_WarnUnusedRecordWildcards) noHints $ - wildcardDoc $ text "No variables bound in the record wildcard match are used" - -redundantWildcardWarning :: SDoc -redundantWildcardWarning = - wildcardDoc $ text "Record wildcard does not bind any new variables" - -wildcardDoc :: SDoc -> SDoc -wildcardDoc herald = - herald - $$ nest 2 (text "Possible fix" <> colon <+> text "omit the" - <+> quotes (text "..")) - {- Note [Skipping ambiguity errors at use sites of local declarations] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -560,78 +514,23 @@ addNameClashErrRn rdr_name gres num_flds = length flds num_non_flds = length non_flds -mkNameClashErr :: Outputable a - => a -> NE.NonEmpty GlobalRdrElt -> TcRnMessage -mkNameClashErr rdr_name gres = - mkTcRnUnknownMessage $ mkPlainError noHints $ - (vcat [ text "Ambiguous occurrence" <+> quotes (ppr rdr_name) - , text "It could refer to" - , nest 3 (vcat (msg1 : msgs)) ]) - where - np1 NE.:| nps = gres - msg1 = text "either" <+> ppr_gre np1 - msgs = [text " or" <+> ppr_gre np | np <- nps] - ppr_gre gre = sep [ pp_gre_name gre <> comma - , pprNameProvenance gre] - - -- When printing the name, take care to qualify it in the same - -- way as the provenance reported by pprNameProvenance, namely - -- the head of 'gre_imp'. Otherwise we get confusing reports like - -- Ambiguous occurrence ‘null’ - -- It could refer to either ‘T15487a.null’, - -- imported from ‘Prelude’ at T15487.hs:1:8-13 - -- or ... - -- See #15487 - pp_gre_name gre - | isRecFldGRE gre - = text "the field" <+> quotes (ppr occ) <+> parent_info - | otherwise - = quotes (pp_qual <> dot <> ppr occ) - where - occ = greOccName gre - parent_info = case gre_par gre of - NoParent -> empty - ParentIs { par_is = par_name } -> text "of record" <+> quotes (ppr par_name) - pp_qual - | gre_lcl gre - = ppr (nameModule $ greName gre) - | Just imp <- headMaybe $ gre_imp gre - -- This 'imp' is the one that - -- pprNameProvenance chooses - , ImpDeclSpec { is_as = mod } <- is_decl imp - = ppr mod - | otherwise - = pprPanic "addNameClassErrRn" (ppr gre) - -- Invariant: either 'lcl' is True or 'iss' is non-empty - - -dupNamesErr :: Outputable n => (n -> SrcSpan) -> NE.NonEmpty n -> RnM () -dupNamesErr get_loc names - = addErrAt big_loc $ mkTcRnUnknownMessage $ mkPlainError noHints $ - vcat [text "Conflicting definitions for" <+> quotes (ppr (NE.head names)), - locations] +mkNameClashErr :: RdrName -> NE.NonEmpty GlobalRdrElt -> TcRnMessage +mkNameClashErr rdr_name gres = TcRnAmbiguousName rdr_name gres + +dupNamesErr :: NE.NonEmpty SrcSpan -> NE.NonEmpty RdrName -> RnM () +dupNamesErr locs names + = addErrAt big_loc (TcRnBindingNameConflict (NE.head names) locs) where - locs = map get_loc (NE.toList names) - big_loc = foldr1 combineSrcSpans locs - locations = text "Bound at:" <+> vcat (map ppr (sortBy SrcLoc.leftmost_smallest locs)) + big_loc = foldr1 combineSrcSpans locs badQualBndrErr :: RdrName -> TcRnMessage -badQualBndrErr rdr_name - = mkTcRnUnknownMessage $ mkPlainError noHints $ - text "Qualified name in binding position:" <+> ppr rdr_name +badQualBndrErr rdr_name = TcRnQualifiedBinder rdr_name -typeAppErr :: String -> LHsType GhcPs -> TcRnMessage -typeAppErr what (L _ k) - = mkTcRnUnknownMessage $ mkPlainError noHints $ - hang (text "Illegal visible" <+> text what <+> text "application" - <+> quotes (char '@' <> ppr k)) - 2 (text "Perhaps you intended to use TypeApplications") +typeAppErr :: TypeOrKind -> LHsType GhcPs -> TcRnMessage +typeAppErr what (L _ k) = TcRnTypeApplicationsDisabled what k badFieldConErr :: Name -> FieldLabelString -> TcRnMessage -badFieldConErr con field - = mkTcRnUnknownMessage $ mkPlainError noHints $ - hsep [text "Constructor" <+> quotes (ppr con), - text "does not have field", quotes (ppr field)] +badFieldConErr con field = TcRnInvalidRecordField con field -- | Ensure that a boxed or unboxed tuple has arity no larger than -- 'mAX_TUPLE_SIZE'. @@ -640,10 +539,7 @@ checkTupSize tup_size | tup_size <= mAX_TUPLE_SIZE = return () | otherwise - = addErr $ mkTcRnUnknownMessage $ mkPlainError noHints $ - sep [text "A" <+> int tup_size <> text "-tuple is too large for GHC", - nest 2 (parens (text "max size is" <+> int mAX_TUPLE_SIZE)), - nest 2 (text "Workaround: use nested tuples or define a data type")] + = addErr (TcRnTupleTooLarge tup_size) -- | Ensure that a constraint tuple has arity no larger than 'mAX_CTUPLE_SIZE'. checkCTupSize :: Int -> TcM () @@ -651,10 +547,7 @@ checkCTupSize tup_size | tup_size <= mAX_CTUPLE_SIZE = return () | otherwise - = addErr $ mkTcRnUnknownMessage $ mkPlainError noHints $ - hang (text "Constraint tuple arity too large:" <+> int tup_size - <+> parens (text "max arity =" <+> int mAX_CTUPLE_SIZE)) - 2 (text "Instead, use a nested tuple") + = addErr (TcRnCTupleTooLarge tup_size) {- ********************************************************************* * * diff --git a/compiler/GHC/Tc/Errors/Ppr.hs b/compiler/GHC/Tc/Errors/Ppr.hs index ef00752196bf..751a5f76821c 100644 --- a/compiler/GHC/Tc/Errors/Ppr.hs +++ b/compiler/GHC/Tc/Errors/Ppr.hs @@ -86,6 +86,7 @@ import GHC.Data.Bag import GHC.Data.FastString import GHC.Data.List.SetOps ( nubOrdBy ) import GHC.Data.Maybe +import GHC.Settings.Constants (mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE) import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic @@ -1790,6 +1791,74 @@ instance Diagnostic TcRnMessage where TcRnIllegalDataCon name -> mkSimpleDecorated $ hsep [text "Illegal data constructor name", quotes (ppr name)] + TcRnNestedForallsContexts entity + -> mkSimpleDecorated $ + what <+> text "cannot contain nested" + <+> quotes forAllLit <> text "s or contexts" + where + what = case entity of + NFC_Specialize -> text "SPECIALISE instance type" + NFC_ViaType -> quotes (text "via") <+> text "type" + NFC_GadtConSig -> text "GADT constructor type signature" + NFC_InstanceHead -> text "Instance head" + NFC_StandaloneDerivedInstanceHead -> text "Standalone-derived instance head" + NFC_DerivedClassType -> text "Derived class type" + TcRnRedundantRecordWildcard + -> mkSimpleDecorated $ + text "Record wildcard does not bind any new variables" + TcRnUnusedRecordWildcard _ + -> mkSimpleDecorated $ + text "No variables bound in the record wildcard match are used" + TcRnUnusedName name reason + -> mkSimpleDecorated $ + pprUnusedName name reason + TcRnQualifiedBinder rdr_name + -> mkSimpleDecorated $ + text "Qualified name in binding position:" <+> ppr rdr_name + TcRnTypeApplicationsDisabled tok t + -> mkSimpleDecorated $ + text "Illegal visible" <+> text what <+> text "application" + <+> quotes (char '@' <> ppr t) + where + what = case tok of + TypeLevel -> "type" + KindLevel -> "kind" + TcRnInvalidRecordField con field + -> mkSimpleDecorated $ + hsep [text "Constructor" <+> quotes (ppr con), + text "does not have field", quotes (ppr field)] + TcRnTupleTooLarge tup_size + -> mkSimpleDecorated $ + sep [text "A" <+> int tup_size <> text "-tuple is too large for GHC", + nest 2 (parens (text "max size is" <+> int mAX_TUPLE_SIZE)), + nest 2 (text "Workaround: use nested tuples or define a data type")] + TcRnCTupleTooLarge tup_size + -> mkSimpleDecorated $ + hang (text "Constraint tuple arity too large:" <+> int tup_size + <+> parens (text "max arity =" <+> int mAX_CTUPLE_SIZE)) + 2 (text "Instead, use a nested tuple") + TcRnIllegalInferredTyVars _ + -> mkSimpleDecorated $ + text "Inferred type variables are not allowed" + TcRnAmbiguousName name gres + -> mkSimpleDecorated $ + vcat [ text "Ambiguous occurrence" <+> quotes (ppr name) + , text "It could refer to" + , nest 3 (vcat (msg1 : msgs)) ] + where + np1 NE.:| nps = gres + msg1 = text "either" <+> ppr_gre np1 + msgs = [text " or" <+> ppr_gre np | np <- nps] + ppr_gre gre = sep [ pprAmbiguousGreName gre <> comma + , pprNameProvenance gre] + TcRnBindingNameConflict name locs + -> mkSimpleDecorated $ + vcat [text "Conflicting definitions for" <+> quotes (ppr name), + locations] + where + locations = + text "Bound at:" + <+> vcat (map ppr (sortBy leftmost_smallest (NE.toList locs))) diagnosticReason = \case TcRnUnknownMessage m @@ -2386,7 +2455,35 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnIllegalDataCon{} -> ErrorWithoutFlag - + TcRnNestedForallsContexts{} + -> ErrorWithoutFlag + TcRnRedundantRecordWildcard + -> WarningWithFlag Opt_WarnRedundantRecordWildcards + TcRnUnusedRecordWildcard{} + -> WarningWithFlag Opt_WarnUnusedRecordWildcards + TcRnUnusedName _ prov + -> WarningWithFlag $ case prov of + UnusedNameTopDecl -> Opt_WarnUnusedTopBinds + UnusedNameImported _ -> Opt_WarnUnusedTopBinds + UnusedNameTypePattern -> Opt_WarnUnusedTypePatterns + UnusedNameMatch -> Opt_WarnUnusedMatches + UnusedNameLocalBind -> Opt_WarnUnusedLocalBinds + TcRnQualifiedBinder{} + -> ErrorWithoutFlag + TcRnTypeApplicationsDisabled{} + -> ErrorWithoutFlag + TcRnInvalidRecordField{} + -> ErrorWithoutFlag + TcRnTupleTooLarge{} + -> ErrorWithoutFlag + TcRnCTupleTooLarge{} + -> ErrorWithoutFlag + TcRnIllegalInferredTyVars{} + -> ErrorWithoutFlag + TcRnAmbiguousName{} + -> ErrorWithoutFlag + TcRnBindingNameConflict{} + -> ErrorWithoutFlag diagnosticHints = \case TcRnUnknownMessage m @@ -3024,6 +3121,30 @@ instance Diagnostic TcRnMessage where -> [suggestExtension LangExt.PackageImports] TcRnIllegalDataCon{} -> noHints + TcRnNestedForallsContexts{} + -> noHints + TcRnRedundantRecordWildcard + -> [SuggestRemoveRecordWildcard] + TcRnUnusedRecordWildcard{} + -> [SuggestRemoveRecordWildcard] + TcRnUnusedName{} + -> noHints + TcRnQualifiedBinder{} + -> noHints + TcRnTypeApplicationsDisabled{} + -> [suggestExtension LangExt.TypeApplications] + TcRnInvalidRecordField{} + -> noHints + TcRnTupleTooLarge{} + -> noHints + TcRnCTupleTooLarge{} + -> noHints + TcRnIllegalInferredTyVars{} + -> noHints + TcRnAmbiguousName{} + -> noHints + TcRnBindingNameConflict{} + -> noHints diagnosticCode :: TcRnMessage -> Maybe DiagnosticCode diagnosticCode = constructorCode @@ -5280,3 +5401,53 @@ pprUnusedImport decl = \case case par of ParentIs p -> pprNameUnqualified p <> parens (ppr fld_occ) NoParent -> ppr fld_occ + +pprUnusedName :: OccName -> UnusedNameProv -> SDoc +pprUnusedName name reason = + sep [ msg <> colon + , nest 2 $ pprNonVarNameSpace (occNameSpace name) + <+> quotes (ppr name)] + where + msg = case reason of + UnusedNameTopDecl -> + defined + UnusedNameImported mod -> + text "Imported from" <+> quotes (ppr mod) <+> text "but not used" + UnusedNameTypePattern -> + defined <+> text "on the right hand side" + UnusedNameMatch -> + defined + UnusedNameLocalBind -> + defined + defined = text "Defined but not used" + +-- When printing the name, take care to qualify it in the same +-- way as the provenance reported by pprNameProvenance, namely +-- the head of 'gre_imp'. Otherwise we get confusing reports like +-- Ambiguous occurrence ‘null’ +-- It could refer to either ‘T15487a.null’, +-- imported from ‘Prelude’ at T15487.hs:1:8-13 +-- or ... +-- See #15487 +pprAmbiguousGreName :: GlobalRdrElt -> SDoc +pprAmbiguousGreName gre + | isRecFldGRE gre + = text "the field" <+> quotes (ppr occ) <+> parent_info + | otherwise + = quotes (pp_qual <> dot <> ppr occ) + where + occ = greOccName gre + parent_info = case gre_par gre of + NoParent -> empty + ParentIs { par_is = par_name } -> text "of record" <+> quotes (ppr par_name) + pp_qual + | gre_lcl gre + = ppr (nameModule $ greName gre) + | Just imp <- headMaybe $ gre_imp gre + -- This 'imp' is the one that + -- pprNameProvenance chooses + , ImpDeclSpec { is_as = mod } <- is_decl imp + = ppr mod + | otherwise + = pprPanic "addNameClassErrRn" (ppr gre) + -- Invariant: either 'lcl' is True or 'iss' is non-empty diff --git a/compiler/GHC/Tc/Errors/Types.hs b/compiler/GHC/Tc/Errors/Types.hs index 9e017a6e52cf..23dc2cd3b030 100644 --- a/compiler/GHC/Tc/Errors/Types.hs +++ b/compiler/GHC/Tc/Errors/Types.hs @@ -114,6 +114,8 @@ module GHC.Tc.Errors.Types ( , ImportLookupReason (..) , UnusedImportReason (..) , UnusedImportName (..) + , NestedForallsContextsIn(..) + , UnusedNameProv(..) ) where import GHC.Prelude @@ -139,7 +141,7 @@ import qualified GHC.Types.Name.Occurrence as OccName import GHC.Types.Name.Reader import GHC.Types.SrcLoc import GHC.Types.TyThing (TyThing) -import GHC.Types.Var (Id, TyCoVar, TyVar, TcTyVar, CoVar) +import GHC.Types.Var (Id, TyCoVar, TyVar, TcTyVar, CoVar, Specificity) import GHC.Types.Var.Env (TidyEnv) import GHC.Types.Var.Set (TyVarSet, VarSet) import GHC.Unit.Types (Module) @@ -3907,6 +3909,134 @@ data TcRnMessage where TcRnIllegalDataCon :: !RdrName -- ^ The constructor name -> TcRnMessage + {-| TcRnNestedForallsContexts is an error indicating that multiple foralls or + contexts are nested/curried where this is not supported, + like @∀ x. ∀ y.@ instead of @∀ x y.@. + + Test cases: + T12087, T14320, T16114, T16394, T16427, T18191, T18240a, T18240b, T18455, T5951 + -} + TcRnNestedForallsContexts :: !NestedForallsContextsIn -> TcRnMessage + + {-| TcRnRedundantRecordWildcard is a warning indicating that a pattern uses + a record wildcard even though all of the record's fields are bound explicitly. + + Test cases: + T15957_Fail + -} + TcRnRedundantRecordWildcard :: TcRnMessage + + {-| TcRnUnusedRecordWildcard is a warning indicating that a pattern uses + a record wildcard while none of the fields bound by it are used. + + Test cases: + T15957_Fail + -} + TcRnUnusedRecordWildcard :: ![Name] -- ^ The names bound by the wildcard + -> TcRnMessage + + {-| TcRnUnusedName is a warning indicating that a defined or imported name + is not used in the module. + + Test cases: + ds053, mc10, overloadedrecfldsfail05, overloadedrecfldsfail06, prog018, + read014, rn040, rn041, rn047, rn063, T13839, T13839a, T13919, T17171b, + T17a, T17b, T17d, T17e, T18470, T1972, t22391, t22391j, T2497, T3371, + T3449, T7145b, T7336, TH_recover_warns, unused_haddock, WarningGroups, + werror + -} + TcRnUnusedName :: !OccName -- ^ The unused name + -> !UnusedNameProv -- ^ The provenance of the name + -> TcRnMessage + + {-| TcRnQualifiedBinder is an error indicating that a qualified name + was used in binding position. + + Test cases: + mod62, rnfail021, rnfail034, rnfail039, rnfail046 + -} + TcRnQualifiedBinder :: !RdrName -- ^ The name used as a binder + -> TcRnMessage + + {-| TcRnTypeApplicationsDisabled is an error indicating that a type + application was used while the extension TypeApplications was disabled. + + Test cases: + T12411, T12446, T15527, T16133, T18251c + -} + TcRnTypeApplicationsDisabled :: !TypeOrKind -- ^ Type or kind application + -> !(HsType GhcPs) -- ^ The type being applied + -> TcRnMessage + + {-| TcRnInvalidRecordField is an error indicating that a record field was + used that doesn't exist in a constructor. + + Test cases: + T13644, T13847, T17469, T8448, T8570, tcfail083, tcfail084 + -} + TcRnInvalidRecordField :: !Name -- ^ The constructor name + -> !FieldLabelString -- ^ The name of the field + -> TcRnMessage + + {-| TcRnTupleTooLarge is an error indicating that the arity of a tuple + exceeds mAX_TUPLE_SIZE. + + Test cases: + T18723a, T18723b, T18723c, T6148a, T6148b, T6148c, T6148d + -} + TcRnTupleTooLarge :: !Int -- ^ The arity of the tuple + -> TcRnMessage + + {-| TcRnCTupleTooLarge is an error indicating that the arity of a constraint + tuple exceeds mAX_CTUPLE_SIZE. + + Test cases: + T10451 + -} + TcRnCTupleTooLarge :: !Int -- ^ The arity of the constraint tuple + -> TcRnMessage + + {-| TcRnIllegalInferredTyVars is an error indicating that some type variables + were quantified as inferred (like @∀ {a}.@) in a place where this is not + allowed, like in an instance declaration. + + Test cases: + ExplicitSpecificity5, ExplicitSpecificity6, ExplicitSpecificity8, + ExplicitSpecificity9 + -} + TcRnIllegalInferredTyVars :: !(NE.NonEmpty (HsTyVarBndr Specificity GhcPs)) + -- ^ The offending type variables + -> TcRnMessage + + {-| TcRnAmbiguousName is an error indicating that an unbound name + might refer to multiple names in scope. + + Test cases: + BootFldReexport, DRFUnused, duplicaterecfldsghci01, GHCiDRF, mod110, + mod151, mod152, mod153, mod164, mod165, NoFieldSelectorsFail, + overloadedrecfldsfail02, overloadedrecfldsfail04, overloadedrecfldsfail11, + overloadedrecfldsfail12, overloadedrecfldsfail13, + overloadedrecfldswasrunnowfail06, rnfail044, T11167_ambig, + T11167_ambiguous_fixity, T13132_duplicaterecflds, T15487, T16745, T17420, + T18999_NoDisambiguateRecordFields, T19397E1, T19397E2, T23010_fail, + tcfail037 + -} + TcRnAmbiguousName :: !RdrName -- ^ The name + -> !(NE.NonEmpty GlobalRdrElt) -- ^ The possible matches + -> TcRnMessage + + {-| TcRnBindingNameConflict is an error indicating that multiple local or + top-level bindings have the same name. + + Test cases: + dsrun006, mdofail002, mdofail003, mod23, mod24, qq006, rnfail001, + rnfail004, SimpleFail6, T14114, T16110_Fail1, tcfail038, TH_spliceD1 + -} + TcRnBindingNameConflict :: !RdrName -- ^ The conflicting name + -> !(NE.NonEmpty SrcSpan) + -- ^ The locations of the duplicates + -> TcRnMessage + deriving Generic -- | Things forbidden in @type data@ declarations. @@ -5414,3 +5544,26 @@ data UnusedImportReason where UnusedImportSome :: ![UnusedImportName] -- ^ The unsed names -> UnusedImportReason deriving (Generic) + +-- | Different places in which a nested foralls/contexts error might occur. +data NestedForallsContextsIn + -- | Nested forall in @SPECIALISE instance@ + = NFC_Specialize + -- | Nested forall in @deriving via@ (via-type) + | NFC_ViaType + -- | Nested forall in the type of a GADT constructor + | NFC_GadtConSig + -- | Nested forall in an instance head + | NFC_InstanceHead + -- | Nested forall in a standalone deriving instance head + | NFC_StandaloneDerivedInstanceHead + -- | Nested forall in deriving class type + | NFC_DerivedClassType + +-- | Provenance of an unused name. +data UnusedNameProv + = UnusedNameTopDecl + | UnusedNameImported !ModuleName + | UnusedNameTypePattern + | UnusedNameMatch + | UnusedNameLocalBind diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs index 1b023400613f..637baba3b668 100644 --- a/compiler/GHC/Tc/Module.hs +++ b/compiler/GHC/Tc/Module.hs @@ -989,7 +989,7 @@ checkHiBootIface' -- At least 2 matches: report an ambiguity error. (gre1,_):(gre2,_):gres_ids -> do addErrAt (nameSrcSpan missing_name) $ - mkNameClashErr missing_name (gre1 NE.:| gre2 : map fst gres_ids) + mkNameClashErr (nameRdrName missing_name) (gre1 NE.:| gre2 : map fst gres_ids) return Nothing -- Single match: resolve the issue. diff --git a/compiler/GHC/Types/Error/Codes.hs b/compiler/GHC/Types/Error/Codes.hs index 46597c8e0ce3..cb80f713d413 100644 --- a/compiler/GHC/Types/Error/Codes.hs +++ b/compiler/GHC/Types/Error/Codes.hs @@ -586,6 +586,18 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnDuplicateDecls" = 29916 GhcDiagnosticCode "TcRnPackageImportsDisabled" = 10032 GhcDiagnosticCode "TcRnIllegalDataCon" = 78448 + GhcDiagnosticCode "TcRnNestedForallsContexts" = 71492 + GhcDiagnosticCode "TcRnRedundantRecordWildcard" = 15932 + GhcDiagnosticCode "TcRnUnusedRecordWildcard" = 83475 + GhcDiagnosticCode "TcRnUnusedName" = 40910 + GhcDiagnosticCode "TcRnQualifiedBinder" = 28329 + GhcDiagnosticCode "TcRnTypeApplicationsDisabled" = 23482 + GhcDiagnosticCode "TcRnInvalidRecordField" = 53822 + GhcDiagnosticCode "TcRnTupleTooLarge" = 94803 + GhcDiagnosticCode "TcRnCTupleTooLarge" = 89347 + GhcDiagnosticCode "TcRnIllegalInferredTyVars" = 54832 + GhcDiagnosticCode "TcRnAmbiguousName" = 87543 + GhcDiagnosticCode "TcRnBindingNameConflict" = 10498 -- PatSynInvalidRhsReason GhcDiagnosticCode "PatSynNotInvertible" = 69317 diff --git a/compiler/GHC/Types/Hint.hs b/compiler/GHC/Types/Hint.hs index 4ce8d04a9d70..773ed4941d4d 100644 --- a/compiler/GHC/Types/Hint.hs +++ b/compiler/GHC/Types/Hint.hs @@ -434,6 +434,11 @@ data GhcHint -} | SuggestSafeHaskell + {-| Suggest removing a record wildcard from a pattern when it doesn't + bind anything useful. + -} + | SuggestRemoveRecordWildcard + -- | An 'InstantiationSuggestion' for a '.hsig' file. This is generated -- by GHC in case of a 'DriverUnexpectedSignature' and suggests a way -- to instantiate a particular signature, where the first argument is diff --git a/compiler/GHC/Types/Hint/Ppr.hs b/compiler/GHC/Types/Hint/Ppr.hs index c0945f29fe32..76e678bb3620 100644 --- a/compiler/GHC/Types/Hint/Ppr.hs +++ b/compiler/GHC/Types/Hint/Ppr.hs @@ -232,6 +232,8 @@ instance Outputable GhcHint where pp_args = hsep (map ppr args) SuggestSafeHaskell -> text "Enable Safe Haskell through either Safe, Trustworthy or Unsafe." + SuggestRemoveRecordWildcard + -> text "Omit the" <+> quotes (text "..") perhapsAsPat :: SDoc perhapsAsPat = text "Perhaps you meant an as-pattern, which must not be surrounded by whitespace" diff --git a/testsuite/tests/deSugar/should_compile/ds053.stderr b/testsuite/tests/deSugar/should_compile/ds053.stderr index 841c6da753db..563503db6314 100644 --- a/testsuite/tests/deSugar/should_compile/ds053.stderr +++ b/testsuite/tests/deSugar/should_compile/ds053.stderr @@ -1,3 +1,3 @@ -ds053.hs:5:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +ds053.hs:5:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘f’ diff --git a/testsuite/tests/deriving/should_compile/T13919.stderr b/testsuite/tests/deriving/should_compile/T13919.stderr index 02cfb71aaa8f..10780d6c366c 100644 --- a/testsuite/tests/deriving/should_compile/T13919.stderr +++ b/testsuite/tests/deriving/should_compile/T13919.stderr @@ -1,3 +1,3 @@ -T13919.hs:13:19: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T13919.hs:13:19: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: record field of Foo4 ‘bar4’ diff --git a/testsuite/tests/driver/t22391/t22391.stderr b/testsuite/tests/driver/t22391/t22391.stderr index bdb2abe792d3..22e1592e1aa8 100644 --- a/testsuite/tests/driver/t22391/t22391.stderr +++ b/testsuite/tests/driver/t22391/t22391.stderr @@ -33,7 +33,7 @@ src/Lib.hs:6:1: warning: [GHC-66111] [-Wunused-imports (in -Wextra)] src/Lib.hs:8:1: warning: [GHC-38417] [-Wmissing-signatures (in -Wall)] Top-level binding with no type signature: blah :: Integer -src/Lib.hs:8:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +src/Lib.hs:8:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘blah’ src/Lib.hs:8:8: warning: [GHC-18042] [-Wtype-defaults (in -Wall)] diff --git a/testsuite/tests/driver/t22391/t22391j.stderr b/testsuite/tests/driver/t22391/t22391j.stderr index bdb2abe792d3..22e1592e1aa8 100644 --- a/testsuite/tests/driver/t22391/t22391j.stderr +++ b/testsuite/tests/driver/t22391/t22391j.stderr @@ -33,7 +33,7 @@ src/Lib.hs:6:1: warning: [GHC-66111] [-Wunused-imports (in -Wextra)] src/Lib.hs:8:1: warning: [GHC-38417] [-Wmissing-signatures (in -Wall)] Top-level binding with no type signature: blah :: Integer -src/Lib.hs:8:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +src/Lib.hs:8:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘blah’ src/Lib.hs:8:8: warning: [GHC-18042] [-Wtype-defaults (in -Wall)] diff --git a/testsuite/tests/driver/werror.stderr b/testsuite/tests/driver/werror.stderr index 67cab2d5f9b9..1c5b681c8b19 100644 --- a/testsuite/tests/driver/werror.stderr +++ b/testsuite/tests/driver/werror.stderr @@ -2,7 +2,7 @@ werror.hs:6:1: error: [GHC-38417] [-Wmissing-signatures (in -Wall), Werror=missing-signatures] Top-level binding with no type signature: main :: IO () -werror.hs:7:13: error: [-Wunused-local-binds (in -Wextra, -Wunused-binds), Werror=unused-local-binds] +werror.hs:7:13: error: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds), Werror=unused-local-binds] Defined but not used: ‘main’ werror.hs:7:13: error: [GHC-63397] [-Wname-shadowing (in -Wall), Werror=name-shadowing] @@ -16,7 +16,7 @@ werror.hs:8:1: error: [GHC-94817] [-Wtabs (in -Wdefault), Werror=tabs] werror.hs:10:1: error: [GHC-38417] [-Wmissing-signatures (in -Wall), Werror=missing-signatures] Top-level binding with no type signature: f :: [a1] -> [a2] -werror.hs:10:1: error: [-Wunused-top-binds (in -Wextra, -Wunused-binds), Werror=unused-top-binds] +werror.hs:10:1: error: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds), Werror=unused-top-binds] Defined but not used: ‘f’ werror.hs:10:1: error: [GHC-62161] [-Wincomplete-patterns (in -Wextra), Werror=incomplete-patterns] diff --git a/testsuite/tests/gadt/T12087.stderr b/testsuite/tests/gadt/T12087.stderr index ef0251a00388..7ef702e8e25d 100644 --- a/testsuite/tests/gadt/T12087.stderr +++ b/testsuite/tests/gadt/T12087.stderr @@ -1,20 +1,20 @@ -T12087.hs:6:20: error: +T12087.hs:6:20: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘MkF1’ -T12087.hs:9:25: error: +T12087.hs:9:25: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘MkF2’ -T12087.hs:12:34: error: +T12087.hs:12:34: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘MkF3’ -T12087.hs:15:36: error: +T12087.hs:15:36: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘MkF4’ -T12087.hs:18:25: error: +T12087.hs:18:25: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘MkF5’ diff --git a/testsuite/tests/gadt/T14320.stderr b/testsuite/tests/gadt/T14320.stderr index 9cfb6ed9fca9..e83aef1b46e0 100644 --- a/testsuite/tests/gadt/T14320.stderr +++ b/testsuite/tests/gadt/T14320.stderr @@ -1,4 +1,4 @@ -T14320.hs:17:14: error: +T14320.hs:17:14: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘TEBad’ diff --git a/testsuite/tests/gadt/T16427.stderr b/testsuite/tests/gadt/T16427.stderr index b7288c9cd694..233544d333e2 100644 --- a/testsuite/tests/gadt/T16427.stderr +++ b/testsuite/tests/gadt/T16427.stderr @@ -1,4 +1,4 @@ -T16427.hs:5:26: error: +T16427.hs:5:26: error: [GHC-71492] GADT constructor type signature cannot contain nested ‘forall’s or contexts In the definition of data constructor ‘C’ diff --git a/testsuite/tests/gadt/T18191.stderr b/testsuite/tests/gadt/T18191.stderr index ce877d033281..8e5662bec311 100644 --- a/testsuite/tests/gadt/T18191.stderr +++ b/testsuite/tests/gadt/T18191.stderr @@ -1,24 +1,24 @@ -T18191.hs:6:11: error: +T18191.hs:6:11: error: [GHC-71492] • GADT constructor type signature cannot contain nested ‘forall’s or contexts • In the definition of data constructor ‘MkT’ -T18191.hs:9:11: error: +T18191.hs:9:11: error: [GHC-71492] • GADT constructor type signature cannot contain nested ‘forall’s or contexts • In the definition of data constructor ‘MkS’ -T18191.hs:12:11: error: +T18191.hs:12:11: error: [GHC-71492] • GADT constructor type signature cannot contain nested ‘forall’s or contexts • In the definition of data constructor ‘MkU’ -T18191.hs:15:21: error: +T18191.hs:15:21: error: [GHC-71492] • GADT constructor type signature cannot contain nested ‘forall’s or contexts • In the definition of data constructor ‘MkZ1’ T18191.hs:15:31: error: [GHC-89246] Record syntax is illegal here: {unZ1 :: (a, b)} -T18191.hs:16:19: error: +T18191.hs:16:19: error: [GHC-71492] • GADT constructor type signature cannot contain nested ‘forall’s or contexts • In the definition of data constructor ‘MkZ2’ diff --git a/testsuite/tests/ghci/prog018/prog018.stdout b/testsuite/tests/ghci/prog018/prog018.stdout index 1fff03d7552d..dddc475a4a8f 100644 --- a/testsuite/tests/ghci/prog018/prog018.stdout +++ b/testsuite/tests/ghci/prog018/prog018.stdout @@ -7,7 +7,7 @@ A.hs:5:1: warning: [GHC-62161] [-Wincomplete-patterns (in -Wextra)] In an equation for ‘incompletePattern’: Patterns of type ‘Int’ not matched: p where p is not one of {0} -A.hs:8:15: warning: [-Wunused-matches (in -Wextra)] +A.hs:8:15: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘x’ B.hs:7:1: warning: [GHC-66111] [-Wunused-imports (in -Wextra)] diff --git a/testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.stderr b/testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.stderr index a8aece69ebcf..327f487a8646 100644 --- a/testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.stderr +++ b/testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.stderr @@ -1,12 +1,12 @@ -ExplicitForAllFams2.hs:34:10: warning: [-Wunused-type-patterns] +ExplicitForAllFams2.hs:34:10: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘t’ -ExplicitForAllFams2.hs:35:10: warning: [-Wunused-type-patterns] +ExplicitForAllFams2.hs:35:10: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ -ExplicitForAllFams2.hs:38:6: warning: [-Wunused-type-patterns] +ExplicitForAllFams2.hs:38:6: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘t’ -ExplicitForAllFams2.hs:39:6: warning: [-Wunused-type-patterns] +ExplicitForAllFams2.hs:39:6: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ diff --git a/testsuite/tests/indexed-types/should_compile/T16356_Compile2.stderr b/testsuite/tests/indexed-types/should_compile/T16356_Compile2.stderr index 41fe7794b89a..9c41c884b683 100644 --- a/testsuite/tests/indexed-types/should_compile/T16356_Compile2.stderr +++ b/testsuite/tests/indexed-types/should_compile/T16356_Compile2.stderr @@ -1,18 +1,18 @@ -T16356_Compile2.hs:10:11: warning: [-Wunused-type-patterns] +T16356_Compile2.hs:10:11: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ -T16356_Compile2.hs:10:11: warning: [-Wunused-type-patterns] +T16356_Compile2.hs:10:11: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘j’ -T16356_Compile2.hs:13:15: warning: [-Wunused-type-patterns] +T16356_Compile2.hs:13:15: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘j’ -T16356_Compile2.hs:13:18: warning: [-Wunused-type-patterns] +T16356_Compile2.hs:13:18: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ -T16356_Compile2.hs:16:15: warning: [-Wunused-type-patterns] +T16356_Compile2.hs:16:15: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘j’ -T16356_Compile2.hs:16:18: warning: [-Wunused-type-patterns] +T16356_Compile2.hs:16:18: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ diff --git a/testsuite/tests/indexed-types/should_compile/T16632.stderr b/testsuite/tests/indexed-types/should_compile/T16632.stderr index 1f0aea9a874b..061b25f2d19d 100644 --- a/testsuite/tests/indexed-types/should_compile/T16632.stderr +++ b/testsuite/tests/indexed-types/should_compile/T16632.stderr @@ -1,5 +1,5 @@ -T16632.hs:5:17: warning: [-Wunused-type-patterns] +T16632.hs:5:17: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ | 5 | type instance F Char b Int = () diff --git a/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarnings.stderr b/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarnings.stderr index b3b97f03a540..296fbea612f8 100644 --- a/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarnings.stderr +++ b/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarnings.stderr @@ -1,12 +1,12 @@ -UnusedTyVarWarnings.hs:8:5: warning: [-Wunused-type-patterns] +UnusedTyVarWarnings.hs:8:5: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ -UnusedTyVarWarnings.hs:11:18: warning: [-Wunused-type-patterns] +UnusedTyVarWarnings.hs:11:18: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ -UnusedTyVarWarnings.hs:27:5: warning: [-Wunused-type-patterns] +UnusedTyVarWarnings.hs:27:5: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ -UnusedTyVarWarnings.hs:33:17: warning: [-Wunused-type-patterns] +UnusedTyVarWarnings.hs:33:17: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ diff --git a/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarningsNamedWCs.stderr b/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarningsNamedWCs.stderr index 4801686ae320..e623a73814cd 100644 --- a/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarningsNamedWCs.stderr +++ b/testsuite/tests/indexed-types/should_compile/UnusedTyVarWarningsNamedWCs.stderr @@ -1,12 +1,12 @@ -UnusedTyVarWarningsNamedWCs.hs:8:5: warning: [-Wunused-type-patterns] +UnusedTyVarWarningsNamedWCs.hs:8:5: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ -UnusedTyVarWarningsNamedWCs.hs:11:18: warning: [-Wunused-type-patterns] +UnusedTyVarWarningsNamedWCs.hs:11:18: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ -UnusedTyVarWarningsNamedWCs.hs:27:5: warning: [-Wunused-type-patterns] +UnusedTyVarWarningsNamedWCs.hs:27:5: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘a’ -UnusedTyVarWarningsNamedWCs.hs:33:17: warning: [-Wunused-type-patterns] +UnusedTyVarWarningsNamedWCs.hs:33:17: warning: [GHC-40910] [-Wunused-type-patterns] Defined but not used on the right hand side: type variable ‘b’ diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail6.stderr b/testsuite/tests/indexed-types/should_fail/SimpleFail6.stderr index 92d8db791240..940aca6192ac 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail6.stderr +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail6.stderr @@ -1,5 +1,5 @@ -SimpleFail6.hs:7:11: error: +SimpleFail6.hs:7:11: error: [GHC-10498] Conflicting definitions for ‘a’ Bound at: SimpleFail6.hs:7:11 SimpleFail6.hs:7:13 diff --git a/testsuite/tests/indexed-types/should_fail/T16110_Fail1.stderr b/testsuite/tests/indexed-types/should_fail/T16110_Fail1.stderr index a20bada9207c..6b448d932898 100644 --- a/testsuite/tests/indexed-types/should_fail/T16110_Fail1.stderr +++ b/testsuite/tests/indexed-types/should_fail/T16110_Fail1.stderr @@ -11,7 +11,7 @@ T16110_Fail1.hs:10:32: error: [GHC-76037] T16110_Fail1.hs:10:34: error: [GHC-76037] Not in scope: type variable ‘b’ -T16110_Fail1.hs:13:15: error: +T16110_Fail1.hs:13:15: error: [GHC-10498] Conflicting definitions for ‘dup’ Bound at: T16110_Fail1.hs:13:15-17 T16110_Fail1.hs:13:19-21 diff --git a/testsuite/tests/mdo/should_fail/mdofail002.stderr b/testsuite/tests/mdo/should_fail/mdofail002.stderr index 7c0d7b679c8c..a038fc4630bd 100644 --- a/testsuite/tests/mdo/should_fail/mdofail002.stderr +++ b/testsuite/tests/mdo/should_fail/mdofail002.stderr @@ -1,5 +1,5 @@ -mdofail002.hs:10:9: +mdofail002.hs:10:9: [GHC-10498] Conflicting definitions for ‘x’ Bound at: mdofail002.hs:10:9 mdofail002.hs:11:9 diff --git a/testsuite/tests/mdo/should_fail/mdofail003.stderr b/testsuite/tests/mdo/should_fail/mdofail003.stderr index 6d9741280ebd..d938463bef02 100644 --- a/testsuite/tests/mdo/should_fail/mdofail003.stderr +++ b/testsuite/tests/mdo/should_fail/mdofail003.stderr @@ -1,5 +1,5 @@ -mdofail003.hs:10:9: +mdofail003.hs:10:9: [GHC-10498] Conflicting definitions for ‘x’ Bound at: mdofail003.hs:10:9 mdofail003.hs:11:13 diff --git a/testsuite/tests/module/mod110.stderr b/testsuite/tests/module/mod110.stderr index 6a7ade9c44b8..38e9c79a5440 100644 --- a/testsuite/tests/module/mod110.stderr +++ b/testsuite/tests/module/mod110.stderr @@ -1,5 +1,5 @@ -mod110.hs:11:10: error: +mod110.hs:11:10: error: [GHC-87543] Ambiguous occurrence ‘Eq’ It could refer to either ‘Prelude.Eq’, imported from ‘Prelude’ at mod110.hs:4:1-14 diff --git a/testsuite/tests/module/mod151.stderr b/testsuite/tests/module/mod151.stderr index 265ad86031d0..8bb41459fb0c 100644 --- a/testsuite/tests/module/mod151.stderr +++ b/testsuite/tests/module/mod151.stderr @@ -1,5 +1,5 @@ -mod151.hs:2:20: error: +mod151.hs:2:20: error: [GHC-87543] Ambiguous occurrence ‘id’ It could refer to either ‘Prelude.id’, imported from ‘Prelude’ at mod151.hs:2:8 diff --git a/testsuite/tests/module/mod152.stderr b/testsuite/tests/module/mod152.stderr index 769b45b1c5c1..d60269b7571e 100644 --- a/testsuite/tests/module/mod152.stderr +++ b/testsuite/tests/module/mod152.stderr @@ -1,5 +1,5 @@ -mod152.hs:2:26: error: +mod152.hs:2:26: error: [GHC-87543] Ambiguous occurrence ‘id’ It could refer to either ‘Prelude.id’, imported from ‘Prelude’ at mod152.hs:2:8 diff --git a/testsuite/tests/module/mod153.stderr b/testsuite/tests/module/mod153.stderr index 51f14a486cb1..989b27a77e22 100644 --- a/testsuite/tests/module/mod153.stderr +++ b/testsuite/tests/module/mod153.stderr @@ -1,5 +1,5 @@ -mod153.hs:2:11: error: +mod153.hs:2:11: error: [GHC-87543] Ambiguous occurrence ‘id’ It could refer to either ‘Prelude.id’, imported from ‘Prelude’ at mod153.hs:2:8 diff --git a/testsuite/tests/module/mod164.stderr b/testsuite/tests/module/mod164.stderr index ecdeff806302..d6c0a9eec20a 100644 --- a/testsuite/tests/module/mod164.stderr +++ b/testsuite/tests/module/mod164.stderr @@ -1,5 +1,5 @@ -mod164.hs:9:5: +mod164.hs:9:5: [GHC-87543] Ambiguous occurrence ‘D1’ It could refer to either ‘Mod164_A.D1’, imported from ‘Mod164_A’ at mod164.hs:4:1-15 diff --git a/testsuite/tests/module/mod165.stderr b/testsuite/tests/module/mod165.stderr index 927b36924db6..9ef57d4bbdf4 100644 --- a/testsuite/tests/module/mod165.stderr +++ b/testsuite/tests/module/mod165.stderr @@ -1,5 +1,5 @@ -mod165.hs:9:5: +mod165.hs:9:5: [GHC-87543] Ambiguous occurrence ‘A.D1’ It could refer to either ‘A.D1’, imported from ‘Mod164_A’ at mod165.hs:4:1-20 diff --git a/testsuite/tests/module/mod23.stderr b/testsuite/tests/module/mod23.stderr index 4387fb737a92..e0d8ef994bb3 100644 --- a/testsuite/tests/module/mod23.stderr +++ b/testsuite/tests/module/mod23.stderr @@ -1,5 +1,5 @@ -mod23.hs:3:8: +mod23.hs:3:8: [GHC-10498] Conflicting definitions for ‘a’ Bound at: mod23.hs:3:8 mod23.hs:3:10 diff --git a/testsuite/tests/module/mod24.stderr b/testsuite/tests/module/mod24.stderr index efc5ad5dd012..34b393c41375 100644 --- a/testsuite/tests/module/mod24.stderr +++ b/testsuite/tests/module/mod24.stderr @@ -1,5 +1,5 @@ -mod24.hs:3:8: +mod24.hs:3:8: [GHC-10498] Conflicting definitions for ‘a’ Bound at: mod24.hs:3:8 mod24.hs:3:10 diff --git a/testsuite/tests/module/mod62.stderr b/testsuite/tests/module/mod62.stderr index eab3f938b1f0..94c4797e0ade 100644 --- a/testsuite/tests/module/mod62.stderr +++ b/testsuite/tests/module/mod62.stderr @@ -1,5 +1,5 @@ -mod62.hs:3:9: error: Qualified name in binding position: M.y +mod62.hs:3:9: error: [GHC-28329] Qualified name in binding position: M.y mod62.hs:3:22: error: [GHC-76037] Not in scope: ‘M.y’ diff --git a/testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout b/testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout index c912c3c4ee14..4d4e5817d9af 100644 --- a/testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout +++ b/testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout @@ -1,6 +1,6 @@ GHCiDRF.foo :: T -> Int -<interactive>:1:1: error: +<interactive>:1:1: error: [GHC-87543] Ambiguous occurrence ‘GHCiDRF.bar’ It could refer to either the field ‘bar’ of record ‘T’, defined at GHCiDRF.hs:3:28 @@ -17,7 +17,7 @@ data U = MkU {bar :: Bool} -- Defined at GHCiDRF.hs:4:16 GHCiDRF.foo :: GHCiDRF.T -> Int -<interactive>:1:1: error: +<interactive>:1:1: error: [GHC-87543] Ambiguous occurrence ‘GHCiDRF.bar’ It could refer to either the field ‘bar’, @@ -37,7 +37,7 @@ type GHCiDRF.U :: * data GHCiDRF.U = GHCiDRF.MkU {GHCiDRF.bar :: Bool} -- Defined at GHCiDRF.hs:4:16 -<interactive>:11:1: error: +<interactive>:11:1: error: [GHC-87543] Ambiguous occurrence ‘GHCiDRF.bar’ It could refer to either the field ‘bar’, diff --git a/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout b/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout index b34e509ecc3b..c1bb4c99f048 100644 --- a/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout +++ b/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout @@ -8,7 +8,7 @@ data T a = MkT {foo :: Bool, ...} -- Defined at <interactive>:4:18 True -<interactive>:1:1: error: +<interactive>:1:1: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘S’, defined at <interactive>:3:16 diff --git a/testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr b/testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr index 0830beb7fc49..29d8f451ca84 100644 --- a/testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr +++ b/testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr @@ -1,5 +1,5 @@ -BootFldReexport.hs:8:9: error: +BootFldReexport.hs:8:9: error: [GHC-87543] Ambiguous occurrence ‘fld’ It could refer to either ‘BootFldReexport_N.fld’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/DRFUnused.stderr b/testsuite/tests/overloadedrecflds/should_fail/DRFUnused.stderr index 88e9e6537fbb..81029d6cd3ea 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/DRFUnused.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/DRFUnused.stderr @@ -1,5 +1,5 @@ -DRFUnused.hs:18:5: error: +DRFUnused.hs:18:5: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘S’, defined at DRFUnused.hs:10:16 diff --git a/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr b/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr index 301b6bc4b893..4eb98f37785e 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr @@ -1,5 +1,5 @@ -NoFieldSelectorsFail.hs:9:14: error: +NoFieldSelectorsFail.hs:9:14: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘Foo’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/T11167_ambiguous_fixity.stderr b/testsuite/tests/overloadedrecflds/should_fail/T11167_ambiguous_fixity.stderr index 277a5bd0acbb..8a1691ac2285 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T11167_ambiguous_fixity.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T11167_ambiguous_fixity.stderr @@ -2,7 +2,7 @@ [2 of 3] Compiling T11167_ambiguous_fixity_B ( T11167_ambiguous_fixity_B.hs, T11167_ambiguous_fixity_B.o ) [3 of 3] Compiling T11167_ambiguous_fixity ( T11167_ambiguous_fixity.hs, T11167_ambiguous_fixity.o ) -T11167_ambiguous_fixity.hs:6:16: error: +T11167_ambiguous_fixity.hs:6:16: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘A’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/T13132_duplicaterecflds.stderr b/testsuite/tests/overloadedrecflds/should_fail/T13132_duplicaterecflds.stderr index 11374466ece4..00fbe0899b95 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T13132_duplicaterecflds.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T13132_duplicaterecflds.stderr @@ -1,5 +1,5 @@ -T13132_duplicaterecflds.hs:7:16: error: +T13132_duplicaterecflds.hs:7:16: error: [GHC-87543] Ambiguous occurrence ‘runContT’ It could refer to either the field ‘runContT’ of record ‘ContT’, @@ -13,7 +13,7 @@ T13132_duplicaterecflds.hs:9:11: error: [GHC-46878] namely ‘y’ [infixl 9] in the section: ‘`runContT` x `y` x’ -T13132_duplicaterecflds.hs:9:12: error: +T13132_duplicaterecflds.hs:9:12: error: [GHC-87543] Ambiguous occurrence ‘runContT’ It could refer to either the field ‘runContT’ of record ‘ContT’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/T16745.stderr b/testsuite/tests/overloadedrecflds/should_fail/T16745.stderr index 5969a540e0ea..b4515b8a1965 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T16745.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T16745.stderr @@ -3,7 +3,7 @@ [3 of 4] Compiling T16745D ( T16745D.hs, T16745D.o ) [4 of 4] Compiling T16745A ( T16745A.hs, T16745A.o ) -T16745A.hs:8:9: error: +T16745A.hs:8:9: error: [GHC-87543] Ambiguous occurrence ‘field’ It could refer to either ‘T16745B.field’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/T17420.stderr b/testsuite/tests/overloadedrecflds/should_fail/T17420.stderr index e1db5fa195f6..3a94cd563925 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T17420.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T17420.stderr @@ -1,7 +1,7 @@ [1 of 2] Compiling T17420A ( T17420A.hs, T17420A.o ) [2 of 2] Compiling T17420 ( T17420.hs, T17420.o ) -T17420.hs:6:17: error: +T17420.hs:6:17: error: [GHC-87543] Ambiguous occurrence ‘name’ It could refer to either the field ‘name’ of record ‘Dog’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/T17469.stderr b/testsuite/tests/overloadedrecflds/should_fail/T17469.stderr index 5d93f464896e..2f97d231cd32 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T17469.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T17469.stderr @@ -1,5 +1,5 @@ [1 of 3] Compiling T17469A ( T17469A.hs, T17469A.o ) [2 of 3] Compiling Main ( T17469.hs, T17469.o ) -T17469.hs:6:32: error: +T17469.hs:6:32: error: [GHC-53822] Constructor ‘MkFoo’ does not have field ‘bar’ diff --git a/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr b/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr index f462dcb1870f..7e7939e028e9 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr @@ -1,5 +1,5 @@ -T18999_NoDisambiguateRecordFields.hs:6:13: error: +T18999_NoDisambiguateRecordFields.hs:6:13: error: [GHC-87543] Ambiguous occurrence ‘not’ It could refer to either ‘Prelude.not’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/T23010_fail.stderr b/testsuite/tests/overloadedrecflds/should_fail/T23010_fail.stderr index 61e93b95bb20..6a1b76dae9c0 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T23010_fail.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T23010_fail.stderr @@ -1,5 +1,5 @@ -T23010_fail.hs-boot:7:1: error: +T23010_fail.hs-boot:7:1: error: [GHC-87543] Ambiguous occurrence ‘T23010_fail.fld’ It could refer to either the field ‘fld’ of record ‘A’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail02.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail02.stderr index 6a2756977633..aaf57bd71064 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail02.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail02.stderr @@ -1,5 +1,5 @@ -overloadedrecfldsfail02.hs:8:18: error: +overloadedrecfldsfail02.hs:8:18: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘R’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail04.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail04.stderr index 6aa46697298d..d319ae53f6b5 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail04.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail04.stderr @@ -1,7 +1,7 @@ [1 of 3] Compiling OverloadedRecFldsFail04_A ( OverloadedRecFldsFail04_A.hs, OverloadedRecFldsFail04_A.o ) [2 of 3] Compiling Main ( overloadedrecfldsfail04.hs, overloadedrecfldsfail04.o ) -overloadedrecfldsfail04.hs:9:6: error: +overloadedrecfldsfail04.hs:9:6: error: [GHC-87543] Ambiguous occurrence ‘I.x’ It could refer to either the field ‘x’ of record ‘V’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail05.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail05.stderr index bff9bd544f2c..5e887e33cfe5 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail05.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail05.stderr @@ -1,3 +1,3 @@ -overloadedrecfldsfail05.hs:7:16: error: [-Wunused-top-binds (in -Wextra, -Wunused-binds), Werror=unused-top-binds] +overloadedrecfldsfail05.hs:7:16: error: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds), Werror=unused-top-binds] Defined but not used: record field of MkT ‘foo’ diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr index f1b59db83f4d..d58443045650 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr @@ -1,12 +1,12 @@ [1 of 3] Compiling OverloadedRecFldsFail06_A ( OverloadedRecFldsFail06_A.hs, OverloadedRecFldsFail06_A.o ) -OverloadedRecFldsFail06_A.hs:9:15: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +OverloadedRecFldsFail06_A.hs:9:15: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: data constructor ‘MkUnused’ -OverloadedRecFldsFail06_A.hs:9:42: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +OverloadedRecFldsFail06_A.hs:9:42: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: record field of MkUnused ‘unused2’ -OverloadedRecFldsFail06_A.hs:9:59: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +OverloadedRecFldsFail06_A.hs:9:59: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: record field of MkUnused ‘used_locally’ [2 of 3] Compiling Main ( overloadedrecfldsfail06.hs, overloadedrecfldsfail06.o ) diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail11.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail11.stderr index 54472f4293a1..423472841c1c 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail11.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail11.stderr @@ -1,7 +1,7 @@ [1 of 3] Compiling OverloadedRecFldsFail11_A ( OverloadedRecFldsFail11_A.hs, OverloadedRecFldsFail11_A.o ) [2 of 3] Compiling Main ( overloadedrecfldsfail11.hs, overloadedrecfldsfail11.o ) -overloadedrecfldsfail11.hs:5:15: error: +overloadedrecfldsfail11.hs:5:15: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘S’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail12.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail12.stderr index 28ebc96009eb..a6abb29b1993 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail12.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail12.stderr @@ -1,7 +1,7 @@ [1 of 3] Compiling OverloadedRecFldsFail12_A ( OverloadedRecFldsFail12_A.hs, OverloadedRecFldsFail12_A.o ) [2 of 3] Compiling Main ( overloadedrecfldsfail12.hs, overloadedrecfldsfail12.o ) -overloadedrecfldsfail12.hs:13:5: error: +overloadedrecfldsfail12.hs:13:5: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘T’, @@ -10,7 +10,7 @@ overloadedrecfldsfail12.hs:13:5: error: or the field ‘foo’ of record ‘S’, defined at overloadedrecfldsfail12.hs:6:16 -overloadedrecfldsfail12.hs:16:5: error: +overloadedrecfldsfail12.hs:16:5: error: [GHC-87543] Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’ of record ‘T’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail13.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail13.stderr index 4fb285b3279d..cf9a7a567876 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail13.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail13.stderr @@ -1,5 +1,5 @@ -overloadedrecfldsfail13.hs:10:5: error: +overloadedrecfldsfail13.hs:10:5: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, @@ -7,7 +7,7 @@ overloadedrecfldsfail13.hs:10:5: error: or the field ‘x’ of record ‘T’, defined at overloadedrecfldsfail13.hs:7:16 -overloadedrecfldsfail13.hs:12:5: error: +overloadedrecfldsfail13.hs:12:5: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, @@ -15,7 +15,7 @@ overloadedrecfldsfail13.hs:12:5: error: or the field ‘x’ of record ‘T’, defined at overloadedrecfldsfail13.hs:7:16 -overloadedrecfldsfail13.hs:15:5: error: +overloadedrecfldsfail13.hs:15:5: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, @@ -23,7 +23,7 @@ overloadedrecfldsfail13.hs:15:5: error: or the field ‘x’ of record ‘T’, defined at overloadedrecfldsfail13.hs:7:16 -overloadedrecfldsfail13.hs:18:5: error: +overloadedrecfldsfail13.hs:18:5: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldswasrunnowfail06.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldswasrunnowfail06.stderr index c5f1e431c982..2b90b16f978c 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldswasrunnowfail06.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldswasrunnowfail06.stderr @@ -1,5 +1,5 @@ -overloadedrecfldswasrunnowfail06.hs:11:11: error: +overloadedrecfldswasrunnowfail06.hs:11:11: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, @@ -9,7 +9,7 @@ overloadedrecfldswasrunnowfail06.hs:11:11: error: or the field ‘x’ of record ‘U’, defined at overloadedrecfldswasrunnowfail06.hs:8:18 -overloadedrecfldswasrunnowfail06.hs:13:11: error: +overloadedrecfldswasrunnowfail06.hs:13:11: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, @@ -19,7 +19,7 @@ overloadedrecfldswasrunnowfail06.hs:13:11: error: or the field ‘x’ of record ‘U’, defined at overloadedrecfldswasrunnowfail06.hs:8:18 -overloadedrecfldswasrunnowfail06.hs:15:13: error: +overloadedrecfldswasrunnowfail06.hs:15:13: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, @@ -29,7 +29,7 @@ overloadedrecfldswasrunnowfail06.hs:15:13: error: or the field ‘x’ of record ‘U’, defined at overloadedrecfldswasrunnowfail06.hs:8:18 -overloadedrecfldswasrunnowfail06.hs:21:20: error: +overloadedrecfldswasrunnowfail06.hs:21:20: error: [GHC-87543] Ambiguous occurrence ‘x’ It could refer to either the field ‘x’ of record ‘S’, diff --git a/testsuite/tests/parser/should_compile/read014.stderr b/testsuite/tests/parser/should_compile/read014.stderr index 88ba43d65df2..3187d4d32afc 100644 --- a/testsuite/tests/parser/should_compile/read014.stderr +++ b/testsuite/tests/parser/should_compile/read014.stderr @@ -3,7 +3,7 @@ read014.hs:4:1: warning: [GHC-38417] [-Wmissing-signatures (in -Wall)] Top-level binding with no type signature: ng1 :: Num a => p -> a -> a -read014.hs:4:5: warning: [-Wunused-matches (in -Wextra)] +read014.hs:4:5: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘x’ read014.hs:6:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)] @@ -11,5 +11,5 @@ read014.hs:6:10: warning: [GHC-06201] [-Wmissing-methods (in -Wdefault)] ‘+’, ‘*’, ‘abs’, ‘signum’, and ‘fromInteger’ • In the instance declaration for ‘Num (a, b)’ -read014.hs:8:53: warning: [-Wunused-matches (in -Wextra)] +read014.hs:8:53: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘x’ diff --git a/testsuite/tests/parser/should_fail/T12446.stderr b/testsuite/tests/parser/should_fail/T12446.stderr index 99a6f65e0b8f..6ebcbd79cba0 100644 --- a/testsuite/tests/parser/should_fail/T12446.stderr +++ b/testsuite/tests/parser/should_fail/T12446.stderr @@ -1,4 +1,4 @@ -T12446.hs:4:5: error: +T12446.hs:4:5: error: [GHC-23482] Illegal visible type application ‘@(_ ~ _)’ - Perhaps you intended to use TypeApplications + Suggested fix: Perhaps you intended to use TypeApplications diff --git a/testsuite/tests/parser/should_fail/T18251c.stderr b/testsuite/tests/parser/should_fail/T18251c.stderr index b4f667d5dde0..ab6c5296d329 100644 --- a/testsuite/tests/parser/should_fail/T18251c.stderr +++ b/testsuite/tests/parser/should_fail/T18251c.stderr @@ -1,4 +1,4 @@ -T18251c.hs:4:5: error: +T18251c.hs:4:5: error: [GHC-23482] Illegal visible type application ‘@Int’ - Perhaps you intended to use TypeApplications + Suggested fix: Perhaps you intended to use TypeApplications diff --git a/testsuite/tests/patsyn/should_fail/T14114.stderr b/testsuite/tests/patsyn/should_fail/T14114.stderr index a93b51e8f48a..5b08c9b9396c 100644 --- a/testsuite/tests/patsyn/should_fail/T14114.stderr +++ b/testsuite/tests/patsyn/should_fail/T14114.stderr @@ -1,17 +1,17 @@ -T14114.hs:4:20: error: +T14114.hs:4:20: error: [GHC-10498] • Conflicting definitions for ‘a’ Bound at: T14114.hs:4:20 T14114.hs:4:22 • In a pattern synonym declaration -T14114.hs:5:20: error: +T14114.hs:5:20: error: [GHC-10498] • Conflicting definitions for ‘a’ Bound at: T14114.hs:5:20 T14114.hs:5:22 • In a pattern synonym declaration -T14114.hs:6:20: error: +T14114.hs:6:20: error: [GHC-10498] • Conflicting definitions for ‘a’ Bound at: T14114.hs:6:20 T14114.hs:6:22 diff --git a/testsuite/tests/polykinds/T10451.stderr b/testsuite/tests/polykinds/T10451.stderr index b8c17be28dce..4c8835e48efb 100644 --- a/testsuite/tests/polykinds/T10451.stderr +++ b/testsuite/tests/polykinds/T10451.stderr @@ -1,5 +1,5 @@ -T10451.hs:22:12: error: +T10451.hs:22:12: error: [GHC-89347] • Constraint tuple arity too large: 66 (max arity = 64) Instead, use a nested tuple • In the type ‘(Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, diff --git a/testsuite/tests/quasiquotation/qq006/qq006.stderr b/testsuite/tests/quasiquotation/qq006/qq006.stderr index 3fd0d019e3b2..c3a231705dfc 100644 --- a/testsuite/tests/quasiquotation/qq006/qq006.stderr +++ b/testsuite/tests/quasiquotation/qq006/qq006.stderr @@ -1,5 +1,5 @@ -Main.hs:8:20: error: +Main.hs:8:20: error: [GHC-10498] • Conflicting definitions for ‘x’ Bound at: Main.hs:8:20-28 Main.hs:8:20-28 diff --git a/testsuite/tests/rename/should_compile/T13839.stdout b/testsuite/tests/rename/should_compile/T13839.stdout index a700b1441cc2..0752cb628681 100644 --- a/testsuite/tests/rename/should_compile/T13839.stdout +++ b/testsuite/tests/rename/should_compile/T13839.stdout @@ -1,5 +1,5 @@ -T13839a.hs:10:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T13839a.hs:10:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘nonUsed’ nonUsed :: () nonUsed :: () diff --git a/testsuite/tests/rename/should_compile/T13839a.stderr b/testsuite/tests/rename/should_compile/T13839a.stderr index 84b987364a19..6a5348c28d44 100644 --- a/testsuite/tests/rename/should_compile/T13839a.stderr +++ b/testsuite/tests/rename/should_compile/T13839a.stderr @@ -1,3 +1,3 @@ -T13839a.hs:10:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T13839a.hs:10:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘nonUsed’ diff --git a/testsuite/tests/rename/should_compile/T17a.stderr b/testsuite/tests/rename/should_compile/T17a.stderr index 4e88e2e44079..9503d1578a71 100644 --- a/testsuite/tests/rename/should_compile/T17a.stderr +++ b/testsuite/tests/rename/should_compile/T17a.stderr @@ -1,3 +1,3 @@ -T17a.hs:8:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T17a.hs:8:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘top’ diff --git a/testsuite/tests/rename/should_compile/T17b.stderr b/testsuite/tests/rename/should_compile/T17b.stderr index c94b869401bd..d78dc0bb53b1 100644 --- a/testsuite/tests/rename/should_compile/T17b.stderr +++ b/testsuite/tests/rename/should_compile/T17b.stderr @@ -1,3 +1,3 @@ -T17b.hs:17:12: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +T17b.hs:17:12: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘local’ diff --git a/testsuite/tests/rename/should_compile/T17d.stderr b/testsuite/tests/rename/should_compile/T17d.stderr index 4fbc9ab8a240..1452d3dd1fe6 100644 --- a/testsuite/tests/rename/should_compile/T17d.stderr +++ b/testsuite/tests/rename/should_compile/T17d.stderr @@ -1,3 +1,3 @@ -T17d.hs:14:5: warning: [-Wunused-matches (in -Wextra)] +T17d.hs:14:5: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘match’ diff --git a/testsuite/tests/rename/should_compile/T17e.stderr b/testsuite/tests/rename/should_compile/T17e.stderr index 3e691426eab7..9ec33c846451 100644 --- a/testsuite/tests/rename/should_compile/T17e.stderr +++ b/testsuite/tests/rename/should_compile/T17e.stderr @@ -1,9 +1,9 @@ -T17e.hs:8:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T17e.hs:8:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘top’ T17e.hs:11:11: warning: [GHC-61367] [-Wunused-pattern-binds (in -Wextra, -Wunused-binds)] This pattern-binding binds no variables: True = True -T17e.hs:17:12: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +T17e.hs:17:12: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘local’ diff --git a/testsuite/tests/rename/should_compile/T1972.stderr b/testsuite/tests/rename/should_compile/T1972.stderr index d3d92a213ac2..f2f183d2a7a1 100644 --- a/testsuite/tests/rename/should_compile/T1972.stderr +++ b/testsuite/tests/rename/should_compile/T1972.stderr @@ -9,5 +9,5 @@ T1972.hs:15:3: warning: [GHC-63397] [-Wname-shadowing (in -Wall)] (and originally defined in ‘Data.Traversable’) defined at T1972.hs:17:1 -T1972.hs:21:10: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +T1972.hs:21:10: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘c’ diff --git a/testsuite/tests/rename/should_compile/T3371.stderr b/testsuite/tests/rename/should_compile/T3371.stderr index b56329196520..3ccdac6fbce1 100644 --- a/testsuite/tests/rename/should_compile/T3371.stderr +++ b/testsuite/tests/rename/should_compile/T3371.stderr @@ -1,3 +1,3 @@ -T3371.hs:10:14: warning: [-Wunused-matches (in -Wextra)] +T3371.hs:10:14: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘a’ diff --git a/testsuite/tests/rename/should_compile/T3449.stderr b/testsuite/tests/rename/should_compile/T3449.stderr index afc8d925156c..a53e01af2d07 100644 --- a/testsuite/tests/rename/should_compile/T3449.stderr +++ b/testsuite/tests/rename/should_compile/T3449.stderr @@ -1,3 +1,3 @@ -T3449.hs-boot:8:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T3449.hs-boot:8:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘unused’ diff --git a/testsuite/tests/rename/should_compile/T7145b.stderr b/testsuite/tests/rename/should_compile/T7145b.stderr index 013d93174d8a..4d68c953875d 100644 --- a/testsuite/tests/rename/should_compile/T7145b.stderr +++ b/testsuite/tests/rename/should_compile/T7145b.stderr @@ -1,3 +1,3 @@ -T7145b.hs:7:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T7145b.hs:7:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘pure’ diff --git a/testsuite/tests/rename/should_compile/mc10.stderr b/testsuite/tests/rename/should_compile/mc10.stderr index 285bd34aebd3..f70a1571c11a 100644 --- a/testsuite/tests/rename/should_compile/mc10.stderr +++ b/testsuite/tests/rename/should_compile/mc10.stderr @@ -1,3 +1,3 @@ -mc10.hs:14:11: warning: [-Wunused-matches (in -Wextra)] +mc10.hs:14:11: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘y’ diff --git a/testsuite/tests/rename/should_compile/rn040.stderr b/testsuite/tests/rename/should_compile/rn040.stderr index 01d6a10e1602..735ad91edda1 100644 --- a/testsuite/tests/rename/should_compile/rn040.stderr +++ b/testsuite/tests/rename/should_compile/rn040.stderr @@ -1,6 +1,6 @@ -rn040.hs:6:12: warning: [-Wunused-matches (in -Wextra)] +rn040.hs:6:12: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘y’ -rn040.hs:8:8: warning: [-Wunused-matches (in -Wextra)] +rn040.hs:8:8: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘w’ diff --git a/testsuite/tests/rename/should_compile/rn041.stderr b/testsuite/tests/rename/should_compile/rn041.stderr index 559da82a9848..bc0817b4518a 100644 --- a/testsuite/tests/rename/should_compile/rn041.stderr +++ b/testsuite/tests/rename/should_compile/rn041.stderr @@ -1,9 +1,9 @@ -rn041.hs:7:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +rn041.hs:7:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘f’ -rn041.hs:9:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +rn041.hs:9:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘g’ -rn041.hs:10:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +rn041.hs:10:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘h’ diff --git a/testsuite/tests/rename/should_compile/rn047.stderr b/testsuite/tests/rename/should_compile/rn047.stderr index 17f59a1c2431..9c733ed027b1 100644 --- a/testsuite/tests/rename/should_compile/rn047.stderr +++ b/testsuite/tests/rename/should_compile/rn047.stderr @@ -1,3 +1,3 @@ -rn047.hs:12:11: warning: [-Wunused-matches (in -Wextra)] +rn047.hs:12:11: warning: [GHC-40910] [-Wunused-matches (in -Wextra)] Defined but not used: ‘y’ diff --git a/testsuite/tests/rename/should_compile/rn063.stderr b/testsuite/tests/rename/should_compile/rn063.stderr index ff4d409b36dd..a0bb647c361c 100644 --- a/testsuite/tests/rename/should_compile/rn063.stderr +++ b/testsuite/tests/rename/should_compile/rn063.stderr @@ -1,6 +1,6 @@ -rn063.hs:10:9: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +rn063.hs:10:9: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘x’ -rn063.hs:13:9: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +rn063.hs:13:9: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘y’ diff --git a/testsuite/tests/rename/should_compile/unused_haddock.stderr b/testsuite/tests/rename/should_compile/unused_haddock.stderr index b705fed36b8e..0b25f0638135 100644 --- a/testsuite/tests/rename/should_compile/unused_haddock.stderr +++ b/testsuite/tests/rename/should_compile/unused_haddock.stderr @@ -1,3 +1,3 @@ -unused_haddock.hs:4:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +unused_haddock.hs:4:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘foo’ diff --git a/testsuite/tests/rename/should_fail/T11167_ambig.stderr b/testsuite/tests/rename/should_fail/T11167_ambig.stderr index 74c706441450..f23a6447725a 100644 --- a/testsuite/tests/rename/should_fail/T11167_ambig.stderr +++ b/testsuite/tests/rename/should_fail/T11167_ambig.stderr @@ -1,5 +1,5 @@ -T11167_ambig.hs:10:13: error: +T11167_ambig.hs:10:13: error: [GHC-87543] Ambiguous occurrence ‘runContT’ It could refer to either the field ‘runContT’ of record ‘ContT’, @@ -7,7 +7,7 @@ T11167_ambig.hs:10:13: error: or the field ‘runContT’ of record ‘ContT'’, defined at T11167_ambig.hs:7:32 -T11167_ambig.hs:17:9: error: +T11167_ambig.hs:17:9: error: [GHC-87543] Ambiguous occurrence ‘runContT’ It could refer to either the field ‘runContT’ of record ‘ContT’, diff --git a/testsuite/tests/rename/should_fail/T13644.stderr b/testsuite/tests/rename/should_fail/T13644.stderr index 8443993fd114..64f9abac0057 100644 --- a/testsuite/tests/rename/should_fail/T13644.stderr +++ b/testsuite/tests/rename/should_fail/T13644.stderr @@ -1,5 +1,5 @@ -T13644.hs:6:24: error: +T13644.hs:6:24: error: [GHC-53822] • Constructor ‘FuncId’ does not have field ‘name’ • In the pattern: FuncId {name = nm} In an equation for ‘baseENDECfuncs’: diff --git a/testsuite/tests/rename/should_fail/T13847.stderr b/testsuite/tests/rename/should_fail/T13847.stderr index 52edbf5acf7e..8d8dff5f8a8d 100644 --- a/testsuite/tests/rename/should_fail/T13847.stderr +++ b/testsuite/tests/rename/should_fail/T13847.stderr @@ -1,5 +1,5 @@ -T13847.hs:4:24: error: +T13847.hs:4:24: error: [GHC-53822] • Constructor ‘A.A’ does not have field ‘foo’ • In the second argument of ‘($)’, namely ‘A.A {foo = ()}’ In the second argument of ‘($)’, namely ‘A.foo $ A.A {foo = ()}’ diff --git a/testsuite/tests/rename/should_fail/T15487.stderr b/testsuite/tests/rename/should_fail/T15487.stderr index bb25939f4ba6..a02cbe40c22c 100644 --- a/testsuite/tests/rename/should_fail/T15487.stderr +++ b/testsuite/tests/rename/should_fail/T15487.stderr @@ -1,5 +1,5 @@ -T15487.hs:7:9: error: +T15487.hs:7:9: error: [GHC-87543] Ambiguous occurrence ‘null’ It could refer to either ‘Prelude.null’, diff --git a/testsuite/tests/rename/should_fail/T15957_Fail.stderr b/testsuite/tests/rename/should_fail/T15957_Fail.stderr index 4032c328149e..71d9b4703624 100644 --- a/testsuite/tests/rename/should_fail/T15957_Fail.stderr +++ b/testsuite/tests/rename/should_fail/T15957_Fail.stderr @@ -1,36 +1,36 @@ -T15957_Fail.hs:7:6: error: [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] +T15957_Fail.hs:7:6: error: [GHC-83475] [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] No variables bound in the record wildcard match are used - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:8:9: error: [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] +T15957_Fail.hs:8:9: error: [GHC-83475] [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] No variables bound in the record wildcard match are used - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:9:12: error: [-Wredundant-record-wildcards (in -Wall), Werror=redundant-record-wildcards] +T15957_Fail.hs:9:12: error: [GHC-15932] [-Wredundant-record-wildcards (in -Wall), Werror=redundant-record-wildcards] Record wildcard does not bind any new variables - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:11:11: error: [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] +T15957_Fail.hs:11:11: error: [GHC-83475] [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] No variables bound in the record wildcard match are used - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:12:16: error: [-Wredundant-record-wildcards (in -Wall), Werror=redundant-record-wildcards] +T15957_Fail.hs:12:16: error: [GHC-15932] [-Wredundant-record-wildcards (in -Wall), Werror=redundant-record-wildcards] Record wildcard does not bind any new variables - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:13:15: error: [-Wredundant-record-wildcards (in -Wall), Werror=redundant-record-wildcards] +T15957_Fail.hs:13:15: error: [GHC-15932] [-Wredundant-record-wildcards (in -Wall), Werror=redundant-record-wildcards] Record wildcard does not bind any new variables - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:20:9: error: [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] +T15957_Fail.hs:20:9: error: [GHC-83475] [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] No variables bound in the record wildcard match are used - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:25:9: error: [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] +T15957_Fail.hs:25:9: error: [GHC-83475] [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] No variables bound in the record wildcard match are used - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ -T15957_Fail.hs:31:18: error: [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] +T15957_Fail.hs:31:18: error: [GHC-83475] [-Wunused-record-wildcards (in -Wall), Werror=unused-record-wildcards] No variables bound in the record wildcard match are used - Possible fix: omit the ‘..’ + Suggested fix: Omit the ‘..’ diff --git a/testsuite/tests/rename/should_fail/T16114.stderr b/testsuite/tests/rename/should_fail/T16114.stderr index adbaffc0ef76..8ed4db8192bc 100644 --- a/testsuite/tests/rename/should_fail/T16114.stderr +++ b/testsuite/tests/rename/should_fail/T16114.stderr @@ -1,4 +1,4 @@ -T16114.hs:4:18: error: +T16114.hs:4:18: error: [GHC-71492] Instance head cannot contain nested ‘forall’s or contexts In an instance declaration diff --git a/testsuite/tests/rename/should_fail/T18240a.stderr b/testsuite/tests/rename/should_fail/T18240a.stderr index 165ede31c634..09132691fd06 100644 --- a/testsuite/tests/rename/should_fail/T18240a.stderr +++ b/testsuite/tests/rename/should_fail/T18240a.stderr @@ -1,30 +1,30 @@ -T18240a.hs:11:11: error: +T18240a.hs:11:11: error: [GHC-71492] • Instance head cannot contain nested ‘forall’s or contexts • In an instance declaration T18240a.hs:12:15: error: [GHC-76037] Not in scope: type variable ‘a’ -T18240a.hs:14:11: error: +T18240a.hs:14:11: error: [GHC-71492] • Instance head cannot contain nested ‘forall’s or contexts • In an instance declaration -T18240a.hs:17:11: error: +T18240a.hs:17:11: error: [GHC-71492] • Instance head cannot contain nested ‘forall’s or contexts • In an instance declaration T18240a.hs:18:22: error: [GHC-76037] Not in scope: type variable ‘a’ -T18240a.hs:20:21: error: +T18240a.hs:20:21: error: [GHC-71492] • Instance head cannot contain nested ‘forall’s or contexts • In an instance declaration T18240a.hs:21:24: error: [GHC-76037] Not in scope: type variable ‘b’ -T18240a.hs:23:19: error: +T18240a.hs:23:19: error: [GHC-71492] • Instance head cannot contain nested ‘forall’s or contexts • In an instance declaration diff --git a/testsuite/tests/rename/should_fail/T18240b.stderr b/testsuite/tests/rename/should_fail/T18240b.stderr index 330e5cc72fa2..062f0b23431c 100644 --- a/testsuite/tests/rename/should_fail/T18240b.stderr +++ b/testsuite/tests/rename/should_fail/T18240b.stderr @@ -1,24 +1,24 @@ -T18240b.hs:17:15: error: +T18240b.hs:17:15: error: [GHC-71492] ‘via’ type cannot contain nested ‘forall’s or contexts In a deriving declaration -T18240b.hs:18:24: error: +T18240b.hs:18:24: error: [GHC-71492] ‘via’ type cannot contain nested ‘forall’s or contexts In a deriving declaration -T18240b.hs:19:25: error: +T18240b.hs:19:25: error: [GHC-71492] ‘via’ type cannot contain nested ‘forall’s or contexts In a deriving declaration -T18240b.hs:26:24: error: +T18240b.hs:26:24: error: [GHC-71492] Derived class type cannot contain nested ‘forall’s or contexts In the data type declaration for ‘Bar’ -T18240b.hs:27:33: error: +T18240b.hs:27:33: error: [GHC-71492] Derived class type cannot contain nested ‘forall’s or contexts In the data type declaration for ‘Bar’ -T18240b.hs:28:34: error: +T18240b.hs:28:34: error: [GHC-71492] Derived class type cannot contain nested ‘forall’s or contexts In the data type declaration for ‘Bar’ diff --git a/testsuite/tests/rename/should_fail/T5951.stderr b/testsuite/tests/rename/should_fail/T5951.stderr index f98fb501ed62..19d849c8f799 100644 --- a/testsuite/tests/rename/should_fail/T5951.stderr +++ b/testsuite/tests/rename/should_fail/T5951.stderr @@ -1,4 +1,4 @@ -T5951.hs:9:8: error: +T5951.hs:9:8: error: [GHC-71492] Instance head cannot contain nested ‘forall’s or contexts In an instance declaration diff --git a/testsuite/tests/rename/should_fail/T6148a.stderr b/testsuite/tests/rename/should_fail/T6148a.stderr index e287636d4d03..6160fbf3dfa3 100644 --- a/testsuite/tests/rename/should_fail/T6148a.stderr +++ b/testsuite/tests/rename/should_fail/T6148a.stderr @@ -1,5 +1,5 @@ -T6148a.hs:3:5: error: +T6148a.hs:3:5: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/rename/should_fail/T6148b.stderr b/testsuite/tests/rename/should_fail/T6148b.stderr index 3c5afcd085c1..29d79e8179f6 100644 --- a/testsuite/tests/rename/should_fail/T6148b.stderr +++ b/testsuite/tests/rename/should_fail/T6148b.stderr @@ -1,5 +1,5 @@ -T6148b.hs:3:5: error: +T6148b.hs:3:5: error: [GHC-94803] A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/rename/should_fail/T6148c.stderr b/testsuite/tests/rename/should_fail/T6148c.stderr index a11d23ccac0e..8a2bad555906 100644 --- a/testsuite/tests/rename/should_fail/T6148c.stderr +++ b/testsuite/tests/rename/should_fail/T6148c.stderr @@ -1,5 +1,5 @@ -T6148c.hs:5:6: error: +T6148c.hs:5:6: error: [GHC-94803] A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/rename/should_fail/T6148d.stderr b/testsuite/tests/rename/should_fail/T6148d.stderr index 774c96e54010..f7f132bf28d9 100644 --- a/testsuite/tests/rename/should_fail/T6148d.stderr +++ b/testsuite/tests/rename/should_fail/T6148d.stderr @@ -1,26 +1,26 @@ -T6148d.hs:5:6: error: +T6148d.hs:5:6: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type • In the Template Haskell quotation ''(,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) -T6148d.hs:6:6: error: +T6148d.hs:6:6: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type • In the Template Haskell quotation '(,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) -T6148d.hs:7:6: error: +T6148d.hs:7:6: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type • In the Template Haskell quotation ''(#,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,#) -T6148d.hs:8:6: error: +T6148d.hs:8:6: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/rename/should_fail/T8448.stderr b/testsuite/tests/rename/should_fail/T8448.stderr index 1b3ee56f4790..12018178539b 100644 --- a/testsuite/tests/rename/should_fail/T8448.stderr +++ b/testsuite/tests/rename/should_fail/T8448.stderr @@ -1,2 +1,3 @@ -T8448.hs:5:21: error: Constructor ‘[]’ does not have field ‘r’ +T8448.hs:5:21: error: [GHC-53822] + Constructor ‘[]’ does not have field ‘r’ diff --git a/testsuite/tests/rename/should_fail/rnfail001.stderr b/testsuite/tests/rename/should_fail/rnfail001.stderr index 3046ff10a147..a27ef00de35c 100644 --- a/testsuite/tests/rename/should_fail/rnfail001.stderr +++ b/testsuite/tests/rename/should_fail/rnfail001.stderr @@ -1,5 +1,5 @@ -rnfail001.hs:3:3: +rnfail001.hs:3:3: [GHC-10498] Conflicting definitions for ‘x’ Bound at: rnfail001.hs:3:3 rnfail001.hs:3:5 diff --git a/testsuite/tests/rename/should_fail/rnfail004.stderr b/testsuite/tests/rename/should_fail/rnfail004.stderr index 6e9a61f6eaac..93322679a502 100644 --- a/testsuite/tests/rename/should_fail/rnfail004.stderr +++ b/testsuite/tests/rename/should_fail/rnfail004.stderr @@ -1,10 +1,10 @@ -rnfail004.hs:6:5: +rnfail004.hs:6:5: [GHC-10498] Conflicting definitions for ‘a’ Bound at: rnfail004.hs:6:5 rnfail004.hs:7:10 -rnfail004.hs:7:6: +rnfail004.hs:7:6: [GHC-10498] Conflicting definitions for ‘b’ Bound at: rnfail004.hs:7:6 rnfail004.hs:8:8 diff --git a/testsuite/tests/rename/should_fail/rnfail021.stderr b/testsuite/tests/rename/should_fail/rnfail021.stderr index 1cf26eca36d8..5cb2e4ac1352 100644 --- a/testsuite/tests/rename/should_fail/rnfail021.stderr +++ b/testsuite/tests/rename/should_fail/rnfail021.stderr @@ -1,2 +1,2 @@ -rnfail021.hs:5:2: Qualified name in binding position: Baz.f +rnfail021.hs:5:2: [GHC-28329] Qualified name in binding position: Baz.f diff --git a/testsuite/tests/rename/should_fail/rnfail034.stderr b/testsuite/tests/rename/should_fail/rnfail034.stderr index f385539f7924..4c7113f20cea 100644 --- a/testsuite/tests/rename/should_fail/rnfail034.stderr +++ b/testsuite/tests/rename/should_fail/rnfail034.stderr @@ -1,5 +1,5 @@ -rnfail034.hs:4:11: error: Qualified name in binding position: M.y +rnfail034.hs:4:11: error: [GHC-28329] Qualified name in binding position: M.y rnfail034.hs:4:26: error: [GHC-76037] Not in scope: ‘M.y’ diff --git a/testsuite/tests/rename/should_fail/rnfail039.stderr b/testsuite/tests/rename/should_fail/rnfail039.stderr index 6283dccd33ee..31001fccab81 100644 --- a/testsuite/tests/rename/should_fail/rnfail039.stderr +++ b/testsuite/tests/rename/should_fail/rnfail039.stderr @@ -1,2 +1,2 @@ -rnfail039.hs:11:15: Qualified name in binding position: P.== +rnfail039.hs:11:15: [GHC-28329] Qualified name in binding position: P.== diff --git a/testsuite/tests/rename/should_fail/rnfail044.stderr b/testsuite/tests/rename/should_fail/rnfail044.stderr index 39f7b77056e1..795cee0dfa51 100644 --- a/testsuite/tests/rename/should_fail/rnfail044.stderr +++ b/testsuite/tests/rename/should_fail/rnfail044.stderr @@ -1,5 +1,5 @@ -rnfail044.hs:5:12: error: +rnfail044.hs:5:12: error: [GHC-87543] Ambiguous occurrence ‘splitAt’ It could refer to either ‘Prelude.splitAt’, diff --git a/testsuite/tests/rename/should_fail/rnfail046.stderr b/testsuite/tests/rename/should_fail/rnfail046.stderr index 49cfe356f460..b298acc61081 100644 --- a/testsuite/tests/rename/should_fail/rnfail046.stderr +++ b/testsuite/tests/rename/should_fail/rnfail046.stderr @@ -1,2 +1,2 @@ -rnfail046.hs:4:13: Qualified name in binding position: Map.Map +rnfail046.hs:4:13: [GHC-28329] Qualified name in binding position: Map.Map diff --git a/testsuite/tests/runghc/T17171b.stderr b/testsuite/tests/runghc/T17171b.stderr index 088a4eca00a6..78095c52bfd9 100644 --- a/testsuite/tests/runghc/T17171b.stderr +++ b/testsuite/tests/runghc/T17171b.stderr @@ -1,5 +1,5 @@ -T17171b.hs:4:1: warning: [-Wunused-top-binds] +T17171b.hs:4:1: warning: [GHC-40910] [-Wunused-top-binds] Defined but not used: ‘main’ | 4 | main = putStrLn "NoMain" diff --git a/testsuite/tests/th/T12411.stderr b/testsuite/tests/th/T12411.stderr index be5f843ee29b..4f1f9861a998 100644 --- a/testsuite/tests/th/T12411.stderr +++ b/testsuite/tests/th/T12411.stderr @@ -1,7 +1,7 @@ -T12411.hs:5:1: error: +T12411.hs:5:1: error: [GHC-23482] Illegal visible type application ‘@Q’ - Perhaps you intended to use TypeApplications + Suggested fix: Perhaps you intended to use TypeApplications T12411.hs:5:7: error: [GHC-76037] Not in scope: type constructor or class ‘Q’ diff --git a/testsuite/tests/th/T16133.stderr b/testsuite/tests/th/T16133.stderr index 840f9f066fec..f9e0e5326bd6 100644 --- a/testsuite/tests/th/T16133.stderr +++ b/testsuite/tests/th/T16133.stderr @@ -1,8 +1,8 @@ -T16133.hs:11:2: error: +T16133.hs:11:2: error: [GHC-23482] Illegal visible type application ‘@Int’ - Perhaps you intended to use TypeApplications + Suggested fix: Perhaps you intended to use TypeApplications -T16133.hs:11:2: error: +T16133.hs:11:2: error: [GHC-23482] Illegal visible kind application ‘@Type’ - Perhaps you intended to use TypeApplications + Suggested fix: Perhaps you intended to use TypeApplications diff --git a/testsuite/tests/th/TH_recover_warns.stderr b/testsuite/tests/th/TH_recover_warns.stderr index 848f1b138022..a9a7c39a6525 100644 --- a/testsuite/tests/th/TH_recover_warns.stderr +++ b/testsuite/tests/th/TH_recover_warns.stderr @@ -4,10 +4,10 @@ TH_recover_warns.hs:(9,18)-(10,64): Splicing expression ======> let x = "a" in let x = "b" in x -TH_recover_warns.hs:9:18: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +TH_recover_warns.hs:9:18: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘x’ -TH_recover_warns.hs:10:34: warning: [-Wunused-local-binds (in -Wextra, -Wunused-binds)] +TH_recover_warns.hs:10:34: warning: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘x’ TH_recover_warns.hs:10:49: warning: [GHC-63397] [-Wname-shadowing (in -Wall)] diff --git a/testsuite/tests/th/TH_spliceD1.stderr b/testsuite/tests/th/TH_spliceD1.stderr index 77ae87356241..041f573a4b25 100644 --- a/testsuite/tests/th/TH_spliceD1.stderr +++ b/testsuite/tests/th/TH_spliceD1.stderr @@ -1,5 +1,5 @@ -TH_spliceD1.hs:10:2: error: +TH_spliceD1.hs:10:2: error: [GHC-10498] • Conflicting definitions for ‘c’ Bound at: TH_spliceD1.hs:10:2-6 TH_spliceD1.hs:10:2-6 diff --git a/testsuite/tests/typecheck/should_compile/T18470.stderr b/testsuite/tests/typecheck/should_compile/T18470.stderr index ffefb020d3dd..7d43e3c1c157 100644 --- a/testsuite/tests/typecheck/should_compile/T18470.stderr +++ b/testsuite/tests/typecheck/should_compile/T18470.stderr @@ -1,3 +1,3 @@ -T18470.hs:6:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T18470.hs:6:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: type constructor or class ‘Closed’ diff --git a/testsuite/tests/typecheck/should_compile/T2497.stderr b/testsuite/tests/typecheck/should_compile/T2497.stderr index 581008128b87..43ed0fa72f58 100644 --- a/testsuite/tests/typecheck/should_compile/T2497.stderr +++ b/testsuite/tests/typecheck/should_compile/T2497.stderr @@ -1,3 +1,3 @@ -T2497.hs:22:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)] +T2497.hs:22:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: ‘beq’ diff --git a/testsuite/tests/typecheck/should_fail/ExplicitSpecificity5.stderr b/testsuite/tests/typecheck/should_fail/ExplicitSpecificity5.stderr index c8fa860a57e6..270a1561c618 100644 --- a/testsuite/tests/typecheck/should_fail/ExplicitSpecificity5.stderr +++ b/testsuite/tests/typecheck/should_fail/ExplicitSpecificity5.stderr @@ -1,4 +1,4 @@ -ExplicitSpecificity5.hs:7:1: error: +ExplicitSpecificity5.hs:7:1: error: [GHC-54832] Inferred type variables are not allowed In an instance declaration diff --git a/testsuite/tests/typecheck/should_fail/ExplicitSpecificity6.stderr b/testsuite/tests/typecheck/should_fail/ExplicitSpecificity6.stderr index 326c9b2ae932..db62abcb4b56 100644 --- a/testsuite/tests/typecheck/should_fail/ExplicitSpecificity6.stderr +++ b/testsuite/tests/typecheck/should_fail/ExplicitSpecificity6.stderr @@ -1,8 +1,8 @@ -ExplicitSpecificity6.hs:8:1: error: +ExplicitSpecificity6.hs:8:1: error: [GHC-54832] Inferred type variables are not allowed In an instance declaration -ExplicitSpecificity6.hs:9:3: error: +ExplicitSpecificity6.hs:9:3: error: [GHC-54832] Inferred type variables are not allowed In a SPECIALISE instance pragma diff --git a/testsuite/tests/typecheck/should_fail/ExplicitSpecificity9.stderr b/testsuite/tests/typecheck/should_fail/ExplicitSpecificity9.stderr index 59bb56cf667a..d61d6eeef004 100644 --- a/testsuite/tests/typecheck/should_fail/ExplicitSpecificity9.stderr +++ b/testsuite/tests/typecheck/should_fail/ExplicitSpecificity9.stderr @@ -1,4 +1,4 @@ -ExplicitSpecificity9.hs:6:1: error: +ExplicitSpecificity9.hs:6:1: error: [GHC-54832] Inferred type variables are not allowed In a deriving declaration diff --git a/testsuite/tests/typecheck/should_fail/T15527.stderr b/testsuite/tests/typecheck/should_fail/T15527.stderr index 6729c26bd58e..a71f82583a73 100644 --- a/testsuite/tests/typecheck/should_fail/T15527.stderr +++ b/testsuite/tests/typecheck/should_fail/T15527.stderr @@ -1,4 +1,4 @@ -T15527.hs:5:6: error: +T15527.hs:5:6: error: [GHC-23482] Illegal visible type application ‘@Int’ - Perhaps you intended to use TypeApplications + Suggested fix: Perhaps you intended to use TypeApplications diff --git a/testsuite/tests/typecheck/should_fail/T16394.stderr b/testsuite/tests/typecheck/should_fail/T16394.stderr index 74e5c25ef5bd..af8384ccfedf 100644 --- a/testsuite/tests/typecheck/should_fail/T16394.stderr +++ b/testsuite/tests/typecheck/should_fail/T16394.stderr @@ -1,4 +1,4 @@ -T16394.hs:6:17: error: +T16394.hs:6:17: error: [GHC-71492] Instance head cannot contain nested ‘forall’s or contexts In an instance declaration diff --git a/testsuite/tests/typecheck/should_fail/T18455.stderr b/testsuite/tests/typecheck/should_fail/T18455.stderr index 15d02d190211..909388c0ccb1 100644 --- a/testsuite/tests/typecheck/should_fail/T18455.stderr +++ b/testsuite/tests/typecheck/should_fail/T18455.stderr @@ -1,4 +1,4 @@ -T18455.hs:7:37: error: +T18455.hs:7:37: error: [GHC-71492] SPECIALISE instance type cannot contain nested ‘forall’s or contexts In a SPECIALISE instance pragma diff --git a/testsuite/tests/typecheck/should_fail/T18723a.stderr b/testsuite/tests/typecheck/should_fail/T18723a.stderr index cb599b3737e7..4a46a5b84d6d 100644 --- a/testsuite/tests/typecheck/should_fail/T18723a.stderr +++ b/testsuite/tests/typecheck/should_fail/T18723a.stderr @@ -1,5 +1,5 @@ -T18723a.hs:4:3: error: +T18723a.hs:4:3: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/typecheck/should_fail/T18723b.stderr b/testsuite/tests/typecheck/should_fail/T18723b.stderr index f0f8936b5deb..0b0f62743ec6 100644 --- a/testsuite/tests/typecheck/should_fail/T18723b.stderr +++ b/testsuite/tests/typecheck/should_fail/T18723b.stderr @@ -1,5 +1,5 @@ -T18723b.hs:7:2: error: +T18723b.hs:7:2: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/typecheck/should_fail/T18723c.stderr b/testsuite/tests/typecheck/should_fail/T18723c.stderr index d1245b7758c5..2b9fd7675919 100644 --- a/testsuite/tests/typecheck/should_fail/T18723c.stderr +++ b/testsuite/tests/typecheck/should_fail/T18723c.stderr @@ -1,5 +1,5 @@ -T18723c.hs:5:2: error: +T18723c.hs:5:2: error: [GHC-94803] • A 65-tuple is too large for GHC (max size is 64) Workaround: use nested tuples or define a data type diff --git a/testsuite/tests/typecheck/should_fail/T19397E1.stderr b/testsuite/tests/typecheck/should_fail/T19397E1.stderr index 00c13f2eca8a..066b8f1da40a 100644 --- a/testsuite/tests/typecheck/should_fail/T19397E1.stderr +++ b/testsuite/tests/typecheck/should_fail/T19397E1.stderr @@ -1,5 +1,5 @@ -T19397E1.hs:1:14: error: +T19397E1.hs:1:14: error: [GHC-87543] Ambiguous occurrence ‘main’ It could refer to either ‘T19397S.main’, diff --git a/testsuite/tests/typecheck/should_fail/T19397E2.stderr b/testsuite/tests/typecheck/should_fail/T19397E2.stderr index 4fc507331060..a66e6170ca0e 100644 --- a/testsuite/tests/typecheck/should_fail/T19397E2.stderr +++ b/testsuite/tests/typecheck/should_fail/T19397E2.stderr @@ -1,5 +1,5 @@ -T19397E2.hs:1:1: error: +T19397E2.hs:1:1: error: [GHC-87543] Ambiguous occurrence ‘main’ It could refer to either ‘T19397S.main’, diff --git a/testsuite/tests/typecheck/should_fail/T8570.stderr b/testsuite/tests/typecheck/should_fail/T8570.stderr index 183001b577fd..d8227507e56a 100644 --- a/testsuite/tests/typecheck/should_fail/T8570.stderr +++ b/testsuite/tests/typecheck/should_fail/T8570.stderr @@ -1,5 +1,5 @@ -T8570.hs:6:18: error: +T8570.hs:6:18: error: [GHC-53822] • Constructor ‘Image’ does not have field ‘filepath’ • In the pattern: Image {filepath = x} In a pattern binding: Image {filepath = x} = logo diff --git a/testsuite/tests/typecheck/should_fail/tcfail037.stderr b/testsuite/tests/typecheck/should_fail/tcfail037.stderr index efe74455731e..60432d86269e 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail037.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail037.stderr @@ -1,5 +1,5 @@ -tcfail037.hs:7:11: error: +tcfail037.hs:7:11: error: [GHC-87543] Ambiguous occurrence ‘+’ It could refer to either ‘Prelude.+’, imported from ‘Prelude’ at tcfail037.hs:3:8-17 diff --git a/testsuite/tests/typecheck/should_fail/tcfail038.stderr b/testsuite/tests/typecheck/should_fail/tcfail038.stderr index 2d3e9e5bc9e4..72911531d8f1 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail038.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail038.stderr @@ -1,10 +1,10 @@ -tcfail038.hs:7:11: +tcfail038.hs:7:11: [GHC-10498] Conflicting definitions for ‘==’ Bound at: tcfail038.hs:7:11-12 tcfail038.hs:9:11-12 -tcfail038.hs:8:11: +tcfail038.hs:8:11: [GHC-10498] Conflicting definitions for ‘/=’ Bound at: tcfail038.hs:8:11-12 tcfail038.hs:10:11-12 diff --git a/testsuite/tests/typecheck/should_fail/tcfail083.stderr b/testsuite/tests/typecheck/should_fail/tcfail083.stderr index badd43909d2e..843fbc47c1af 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail083.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail083.stderr @@ -1,5 +1,5 @@ -tcfail083.hs:8:39: +tcfail083.hs:8:39: [GHC-53822] Constructor ‘Bar’ does not have field ‘baz’ In the pattern: Bar {flag = f, baz = b} In the pattern: State {bar = Bar {flag = f, baz = b}} diff --git a/testsuite/tests/typecheck/should_fail/tcfail084.stderr b/testsuite/tests/typecheck/should_fail/tcfail084.stderr index df09cd91bed6..44ec1169b1b5 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail084.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail084.stderr @@ -1,5 +1,5 @@ -tcfail084.hs:10:5: +tcfail084.hs:10:5: [GHC-53822] Constructor ‘F’ does not have field ‘y’ In the expression: F {y = 2} In an equation for ‘z’: z = F {y = 2} diff --git a/testsuite/tests/warnings/should_fail/WarningGroups.stderr b/testsuite/tests/warnings/should_fail/WarningGroups.stderr index 8e9cedb07ec4..bebbf547a374 100644 --- a/testsuite/tests/warnings/should_fail/WarningGroups.stderr +++ b/testsuite/tests/warnings/should_fail/WarningGroups.stderr @@ -2,8 +2,8 @@ WarningGroups.hs:4:1: warning: [GHC-38417] [-Wmissing-signatures (in -Wall)] Top-level binding with no type signature: unused :: () -WarningGroups.hs:4:1: error: [-Wunused-top-binds (in -Wextra, -Wunused-binds), Werror=unused-top-binds] +WarningGroups.hs:4:1: error: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds), Werror=unused-top-binds] Defined but not used: ‘unused’ -WarningGroups.hs:4:14: error: [-Wunused-local-binds (in -Wextra, -Wunused-binds), Werror=unused-local-binds] +WarningGroups.hs:4:14: error: [GHC-40910] [-Wunused-local-binds (in -Wextra, -Wunused-binds), Werror=unused-local-binds] Defined but not used: ‘useless’ -- GitLab