From 99ced73bf5b2f5f82a2e09accbf01eceaa3ce0ca Mon Sep 17 00:00:00 2001 From: Krzysztof Gogolewski <krzysztof.gogolewski@tweag.io> Date: Fri, 10 Nov 2023 21:45:34 +0100 Subject: [PATCH] Remove loopy superclass solve mechanism Programs with a -Wloopy-superclass-solve warning will now fail with an error. Fixes #23017 --- compiler/GHC/Driver/Flags.hs | 3 +- compiler/GHC/Driver/Session.hs | 2 +- compiler/GHC/Tc/Errors/Ppr.hs | 21 ----------- compiler/GHC/Tc/Errors/Types.hs | 17 --------- compiler/GHC/Tc/Solver/Dict.hs | 33 ----------------- compiler/GHC/Tc/TyCl/Instance.hs | 14 -------- compiler/GHC/Tc/Types/Origin.hs-boot | 4 --- compiler/GHC/Types/Error/Codes.hs | 2 +- compiler/GHC/Types/Hint.hs | 5 +-- compiler/GHC/Types/Hint/Ppr.hs | 9 ----- docs/users_guide/using-warnings.rst | 13 +++---- .../typecheck/should_compile/T20666b.stderr | 10 ------ .../typecheck/should_compile/T22891.stderr | 10 ------ .../typecheck/should_compile/T22912.stderr | 12 ------- .../tests/typecheck/should_compile/all.T | 3 -- .../tests/typecheck/should_fail/T20666.stderr | 36 +++++++++---------- .../typecheck/should_fail/T20666a.stderr | 18 +++++----- .../T20666b.hs | 0 .../typecheck/should_fail/T20666b.stderr | 10 ++++++ .../{should_compile => should_fail}/T22891.hs | 0 .../tests/typecheck/should_fail/T22891.stderr | 9 +++++ .../{should_compile => should_fail}/T22912.hs | 0 .../tests/typecheck/should_fail/T22912.stderr | 20 +++++++++++ .../tests/typecheck/should_fail/T6161.stderr | 15 ++++---- testsuite/tests/typecheck/should_fail/all.T | 11 +++--- .../typecheck/should_fail/tcfail223.stderr | 17 +++++---- 26 files changed, 96 insertions(+), 198 deletions(-) delete mode 100644 testsuite/tests/typecheck/should_compile/T20666b.stderr delete mode 100644 testsuite/tests/typecheck/should_compile/T22891.stderr delete mode 100644 testsuite/tests/typecheck/should_compile/T22912.stderr rename testsuite/tests/typecheck/{should_compile => should_fail}/T20666b.hs (100%) create mode 100644 testsuite/tests/typecheck/should_fail/T20666b.stderr rename testsuite/tests/typecheck/{should_compile => should_fail}/T22891.hs (100%) create mode 100644 testsuite/tests/typecheck/should_fail/T22891.stderr rename testsuite/tests/typecheck/{should_compile => should_fail}/T22912.hs (100%) create mode 100644 testsuite/tests/typecheck/should_fail/T22912.stderr diff --git a/compiler/GHC/Driver/Flags.hs b/compiler/GHC/Driver/Flags.hs index 577b015d6148..bf4ac2bc788c 100644 --- a/compiler/GHC/Driver/Flags.hs +++ b/compiler/GHC/Driver/Flags.hs @@ -688,7 +688,7 @@ data WarningFlag = | Opt_WarnGADTMonoLocalBinds -- Since 9.4 | Opt_WarnTypeEqualityOutOfScope -- Since 9.4 | Opt_WarnTypeEqualityRequiresOperators -- Since 9.4 - | Opt_WarnLoopySuperclassSolve -- Since 9.6 + | Opt_WarnLoopySuperclassSolve -- Since 9.6, has no effect since 9.10 | Opt_WarnTermVariableCapture -- Since 9.8 | Opt_WarnMissingRoleAnnotations -- Since 9.8 | Opt_WarnImplicitRhsQuantification -- Since 9.8 @@ -948,7 +948,6 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnForallIdentifier, Opt_WarnUnicodeBidirectionalFormatCharacters, Opt_WarnGADTMonoLocalBinds, - Opt_WarnLoopySuperclassSolve, Opt_WarnBadlyStagedTypes, Opt_WarnTypeEqualityRequiresOperators, Opt_WarnInconsistentFlags, diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index 800bd321a15a..4b5ec2216cdc 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -2198,7 +2198,7 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnInconsistentFlags -> warnSpec x Opt_WarnInlineRuleShadowing -> warnSpec x Opt_WarnIdentities -> warnSpec x - Opt_WarnLoopySuperclassSolve -> warnSpec x + Opt_WarnLoopySuperclassSolve -> depWarnSpec x "it is now an error" Opt_WarnMissingFields -> warnSpec x Opt_WarnMissingImportList -> warnSpec x Opt_WarnMissingExportList -> warnSpec x diff --git a/compiler/GHC/Tc/Errors/Ppr.hs b/compiler/GHC/Tc/Errors/Ppr.hs index 74587d877318..87bed258dfe2 100644 --- a/compiler/GHC/Tc/Errors/Ppr.hs +++ b/compiler/GHC/Tc/Errors/Ppr.hs @@ -1349,18 +1349,6 @@ instance Diagnostic TcRnMessage where , text "Combine alternative minimal complete definitions with `|'" ] where sigs = sig1 : sig2 : otherSigs - TcRnLoopySuperclassSolve wtd_loc wtd_pty -> - mkSimpleDecorated $ vcat [ header, warning, user_manual ] - where - header, warning, user_manual :: SDoc - header - = vcat [ text "I am solving the constraint" <+> quotes (ppr wtd_pty) <> comma - , nest 2 $ pprCtOrigin (ctLocOrigin wtd_loc) <> comma - , text "in a way that might turn out to loop at runtime." ] - warning - = vcat [ text "Starting from GHC 9.10, this warning will turn into an error." ] - user_manual = - vcat [ text "See the user manual, § Undecidable instances and loopy superclasses." ] TcRnUnexpectedStandaloneDerivingDecl -> mkSimpleDecorated $ text "Illegal standalone deriving declaration" TcRnUnusedVariableInRuleDecl name var -> mkSimpleDecorated $ @@ -2311,8 +2299,6 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnDuplicateMinimalSig{} -> ErrorWithoutFlag - TcRnLoopySuperclassSolve{} - -> WarningWithFlag Opt_WarnLoopySuperclassSolve TcRnUnexpectedStandaloneDerivingDecl{} -> ErrorWithoutFlag TcRnUnusedVariableInRuleDecl{} @@ -2962,13 +2948,6 @@ instance Diagnostic TcRnMessage where -> [suggestExtension LangExt.DefaultSignatures] TcRnDuplicateMinimalSig{} -> noHints - TcRnLoopySuperclassSolve wtd_loc wtd_pty - -> [LoopySuperclassSolveHint wtd_pty cls_or_qc] - where - cls_or_qc :: ClsInstOrQC - cls_or_qc = case ctLocOrigin wtd_loc of - ScOrigin c_or_q _ -> c_or_q - _ -> IsClsInst -- shouldn't happen TcRnUnexpectedStandaloneDerivingDecl{} -> [suggestExtension LangExt.StandaloneDeriving] TcRnUnusedVariableInRuleDecl{} diff --git a/compiler/GHC/Tc/Errors/Types.hs b/compiler/GHC/Tc/Errors/Types.hs index 572b44b695c4..be15f54a8ad0 100644 --- a/compiler/GHC/Tc/Errors/Types.hs +++ b/compiler/GHC/Tc/Errors/Types.hs @@ -3134,23 +3134,6 @@ data TcRnMessage where TcRnDeprecatedInvisTyArgInConPat :: TcRnMessage - {-| TcRnLoopySuperclassSolve is a warning, controlled by @-Wloopy-superclass-solve@, - that is triggered when GHC solves a constraint in a possibly-loopy way, - violating the class instance termination rules described in the section - "Undecidable instances and loopy superclasses" of the user's guide. - - Example: - - class Foo f - class Foo f => Bar f g - instance Bar f f => Bar f (h k) - - Test cases: T20666, T20666{a,b}, T22891, T22912. - -} - TcRnLoopySuperclassSolve :: CtLoc -- ^ Wanted 'CtLoc' - -> PredType -- ^ Wanted 'PredType' - -> TcRnMessage - {-| TcRnUnexpectedStandaloneDerivingDecl is an error thrown when a user uses standalone deriving without enabling the StandaloneDeriving extension. diff --git a/compiler/GHC/Tc/Solver/Dict.hs b/compiler/GHC/Tc/Solver/Dict.hs index 03d869fde780..fc6eeb91263b 100644 --- a/compiler/GHC/Tc/Solver/Dict.hs +++ b/compiler/GHC/Tc/Solver/Dict.hs @@ -98,7 +98,6 @@ solveDict dict_ct@(DictCt { di_ev = ev, di_cls = cls, di_tys = tys }) ; doTopFunDepImprovement dict_ct - ; tryLastResortProhibitedSuperClass dict_ct ; simpleStage (updInertDicts dict_ct) ; stopWithStage (dictCtEvidence dict_ct) "Kept inert DictCt" } @@ -1367,38 +1366,6 @@ with the least superclass depth (see Note [Replacement vs keeping]), but that doesn't work for the example from #22216. -} -{- ******************************************************************* -* * - Last resort prohibited superclass -* * -**********************************************************************-} - -tryLastResortProhibitedSuperClass :: DictCt -> SolverStage () --- ^ As a last resort, we TEMPORARILY allow a prohibited superclass solve, --- emitting a loud warning when doing so: we might be creating non-terminating --- evidence (as we are in T22912 for example). --- --- See Note [Migrating away from loopy superclass solving] in GHC.Tc.TyCl.Instance. -tryLastResortProhibitedSuperClass dict_ct - = Stage $ do { inerts <- getInertCans - ; last_resort inerts dict_ct } - -last_resort :: InertCans -> DictCt -> TcS (StopOrContinue ()) -last_resort inerts (DictCt { di_ev = ev_w, di_cls = cls, di_tys = xis }) - | let loc_w = ctEvLoc ev_w - orig_w = ctLocOrigin loc_w - , ScOrigin _ NakedSc <- orig_w -- work_item is definitely Wanted - , Just ct_i <- lookupInertDict inerts loc_w cls xis - , let ev_i = dictCtEvidence ct_i - , isGiven ev_i - = do { setEvBindIfWanted ev_w True (ctEvTerm ev_i) - ; ctLocWarnTcS loc_w $ - TcRnLoopySuperclassSolve loc_w (ctEvPred ev_w) - ; return $ Stop ev_w (text "Loopy superclass") } - | otherwise - = continueWith () - - {- ********************************************************************* * * * Functional dependencies, instantiation of equations diff --git a/compiler/GHC/Tc/TyCl/Instance.hs b/compiler/GHC/Tc/TyCl/Instance.hs index bae9b0fb85d1..4248e1a7ae9f 100644 --- a/compiler/GHC/Tc/TyCl/Instance.hs +++ b/compiler/GHC/Tc/TyCl/Instance.hs @@ -1696,20 +1696,6 @@ Answer: superclass selection, except at a smaller type. This test is implemented by GHC.Tc.Solver.InertSet.prohibitedSuperClassSolve -Note [Migrating away from loopy superclass solving] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The logic from Note [Solving superclass constraints] was implemented in GHC 9.6. -However, we want to provide a migration strategy for users, to avoid suddenly -breaking their code going when upgrading to GHC 9.6. To this effect, we temporarily -continue to allow the constraint solver to create these potentially non-terminating -solutions, but emit a loud warning when doing so: see -GHC.Tc.Solver.Dict.tryLastResortProhibitedSuperclass. - -Users can silence the warning by manually adding the necessary constraint to the -context. GHC will then keep this user-written Given, dropping the Given arising -from superclass expansion which has greater SC depth, as explained in -Note [Replacement vs keeping] in GHC.Tc.Solver.Dict. - Note [Silent superclass arguments] (historical interest only) ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ NB1: this note describes our *old* solution to the diff --git a/compiler/GHC/Tc/Types/Origin.hs-boot b/compiler/GHC/Tc/Types/Origin.hs-boot index d392b3df2453..ff7ab933f100 100644 --- a/compiler/GHC/Tc/Types/Origin.hs-boot +++ b/compiler/GHC/Tc/Types/Origin.hs-boot @@ -16,8 +16,4 @@ data FixedRuntimeRepOrigin mkFRRUnboxedTuple :: Int -> FixedRuntimeRepContext mkFRRUnboxedSum :: Maybe Int -> FixedRuntimeRepContext -data CtOrigin -data ClsInstOrQC = IsClsInst - | IsQC CtOrigin - unkSkol :: HasCallStack => SkolemInfo diff --git a/compiler/GHC/Types/Error/Codes.hs b/compiler/GHC/Types/Error/Codes.hs index dc48b4313109..2acd145599ab 100644 --- a/compiler/GHC/Types/Error/Codes.hs +++ b/compiler/GHC/Types/Error/Codes.hs @@ -520,7 +520,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnMisplacedSigDecl" = 87866 GhcDiagnosticCode "TcRnUnexpectedDefaultSig" = 40700 GhcDiagnosticCode "TcRnDuplicateMinimalSig" = 85346 - GhcDiagnosticCode "TcRnLoopySuperclassSolve" = 36038 + GhcDiagnosticCode "TcRnLoopySuperclassSolve" = Outdated 36038 GhcDiagnosticCode "TcRnUnexpectedStandaloneDerivingDecl" = 95159 GhcDiagnosticCode "TcRnUnusedVariableInRuleDecl" = 65669 GhcDiagnosticCode "TcRnUnexpectedStandaloneKindSig" = 45906 diff --git a/compiler/GHC/Types/Hint.hs b/compiler/GHC/Types/Hint.hs index fe8882eb741f..a4fb6ea2ef6c 100644 --- a/compiler/GHC/Types/Hint.hs +++ b/compiler/GHC/Types/Hint.hs @@ -35,13 +35,12 @@ import GHC.Hs.Extension (GhcTc, GhcRn) import GHC.Core.Coercion import GHC.Core.FamInstEnv (FamFlavor) import GHC.Core.TyCon (TyCon) -import GHC.Core.Type (PredType, Type) +import GHC.Core.Type (Type) import GHC.Types.Fixity (LexicalFixity(..)) import GHC.Types.Name (Name, NameSpace, OccName (occNameFS), isSymOcc, nameOccName) import GHC.Types.Name.Reader (RdrName (Unqual), ImpDeclSpec) import GHC.Types.SrcLoc (SrcSpan) import GHC.Types.Basic (Activation, RuleName) -import {-# SOURCE #-} GHC.Tc.Types.Origin ( ClsInstOrQC(..) ) import GHC.Parser.Errors.Basic import GHC.Utils.Outputable import GHC.Data.FastString (fsLit, FastString) @@ -433,8 +432,6 @@ data GhcHint -} | SuggestRenameTypeVariable - | LoopySuperclassSolveHint PredType ClsInstOrQC - | SuggestExplicitBidiPatSyn Name (LPat GhcRn) [LIdP GhcRn] {-| Suggest enabling one of the SafeHaskell modes Safe, Unsafe or diff --git a/compiler/GHC/Types/Hint/Ppr.hs b/compiler/GHC/Types/Hint/Ppr.hs index 48490b5f027b..30d5ca5ce737 100644 --- a/compiler/GHC/Types/Hint/Ppr.hs +++ b/compiler/GHC/Types/Hint/Ppr.hs @@ -16,7 +16,6 @@ import GHC.Core.FamInstEnv (FamFlavor(..)) import GHC.Core.TyCon import GHC.Core.TyCo.Rep ( mkVisFunTyMany ) import GHC.Hs.Expr () -- instance Outputable -import GHC.Tc.Types.Origin ( ClsInstOrQC(..) ) import GHC.Types.Id import GHC.Types.Name import GHC.Types.Name.Reader (RdrName,ImpDeclSpec (..), rdrNameOcc, rdrNameSpace) @@ -217,14 +216,6 @@ instance Outputable GhcHint where mod = nameModule name SuggestRenameTypeVariable -> text "Consider renaming the type variable." - LoopySuperclassSolveHint pty cls_or_qc - -> vcat [ text "Add the constraint" <+> quotes (ppr pty) <+> text "to the" <+> what <> comma - , text "even though it seems logically implied by other constraints in the context." ] - where - what :: SDoc - what = case cls_or_qc of - IsClsInst -> text "instance context" - IsQC {} -> text "context of the quantified constraint" SuggestExplicitBidiPatSyn name pat args -> hang (text "Instead use an explicitly bidirectional" <+> text "pattern synonym, e.g.") diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 84dcd6721c54..01e5394817c6 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -2422,20 +2422,17 @@ of ``-W(no-)*``. extension. .. ghc-flag:: -Wloopy-superclass-solve - :shortdesc: warn when creating potentially-loopy superclass constraint evidence + :shortdesc: *(deprecated)* warn when creating potentially-loopy superclass constraint evidence :type: dynamic :reverse: -Wno-loopy-superclass-solve :since: 9.6.1 - As explained in :ref:`undecidable-instances`, when using - :extension:`UndecidableInstances` it is possible for GHC to construct + This warning is deprecated. It no longer has any effect since GHC 9.10. + In the past, :extension:`UndecidableInstances` allowed potentially non-terminating evidence for certain superclass constraints. - - This behaviour is scheduled to be removed in a future GHC version. - In the meantime, GHC emits this warning to inform users of potential - non-termination. Users can manually add the required constraint to the context - to avoid the problem (thus silencing the warning). + This is no longer allowed, as explained in :ref:`undecidable-instances`. + This warning was used during the transition period. .. ghc-flag:: -Wterm-variable-capture :shortdesc: warn when an implicitly quantified type variable captures a term's name diff --git a/testsuite/tests/typecheck/should_compile/T20666b.stderr b/testsuite/tests/typecheck/should_compile/T20666b.stderr deleted file mode 100644 index 59445bcf9322..000000000000 --- a/testsuite/tests/typecheck/should_compile/T20666b.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -T20666b.hs:11:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Eq (F [a])’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Eq (F [a])’ to the instance context, - even though it seems logically implied by other constraints in the context. diff --git a/testsuite/tests/typecheck/should_compile/T22891.stderr b/testsuite/tests/typecheck/should_compile/T22891.stderr deleted file mode 100644 index 407868324975..000000000000 --- a/testsuite/tests/typecheck/should_compile/T22891.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -T22891.hs:9:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Foo f’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Foo f’ to the instance context, - even though it seems logically implied by other constraints in the context. diff --git a/testsuite/tests/typecheck/should_compile/T22912.stderr b/testsuite/tests/typecheck/should_compile/T22912.stderr deleted file mode 100644 index 852a1b6896a1..000000000000 --- a/testsuite/tests/typecheck/should_compile/T22912.stderr +++ /dev/null @@ -1,12 +0,0 @@ - -T22912.hs:17:16: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Implies c’, - arising from the head of a quantified constraint - arising from a use of ‘go’, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Implies - c’ to the context of the quantified constraint, - even though it seems logically implied by other constraints in the context. diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 02f2af7302ec..815285482615 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -866,9 +866,6 @@ test('T22647', normal, compile, ['']) test('T19577', normal, compile, ['']) test('T22383', normal, compile, ['']) test('T21501', normal, compile, ['']) -test('T20666b', normal, compile, ['']) -test('T22891', normal, compile, ['']) -test('T22912', normal, compile, ['']) test('T22924', normal, compile, ['']) test('T22985a', normal, compile, ['-O']) test('T22985b', normal, compile, ['']) diff --git a/testsuite/tests/typecheck/should_fail/T20666.stderr b/testsuite/tests/typecheck/should_fail/T20666.stderr index 63a0d11c0766..bc2aad54971a 100644 --- a/testsuite/tests/typecheck/should_fail/T20666.stderr +++ b/testsuite/tests/typecheck/should_fail/T20666.stderr @@ -1,20 +1,20 @@ -T20666.hs:13:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Show (T c)’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Show (T c)’ to the instance context, - even though it seems logically implied by other constraints in the context. +T20666.hs:13:10: error: [GHC-39999] + • Could not deduce ‘Show (T c)’ + arising from the superclasses of an instance declaration + from the context: (D d, c ~ S d) + bound by the instance declaration at T20666.hs:13:10-31 + Possible fix: + If the constraint looks soluble from a superclass of the instance context, + read 'Undecidable instances and loopy superclasses' in the user manual + • In the instance declaration for ‘C1 c’ -T20666.hs:17:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Show (T c)’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Show (T c)’ to the instance context, - even though it seems logically implied by other constraints in the context. +T20666.hs:17:10: error: [GHC-39999] + • Could not deduce ‘Show (T c)’ + arising from the superclasses of an instance declaration + from the context: (D d, c ~ S d, c' ~ c) + bound by the instance declaration at T20666.hs:17:10-40 + Possible fix: + If the constraint looks soluble from a superclass of the instance context, + read 'Undecidable instances and loopy superclasses' in the user manual + • In the instance declaration for ‘C2 c'’ diff --git a/testsuite/tests/typecheck/should_fail/T20666a.stderr b/testsuite/tests/typecheck/should_fail/T20666a.stderr index c4b302294971..4192b88807c7 100644 --- a/testsuite/tests/typecheck/should_fail/T20666a.stderr +++ b/testsuite/tests/typecheck/should_fail/T20666a.stderr @@ -1,10 +1,10 @@ -T20666a.hs:11:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Eq (F [a])’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Eq (F [a])’ to the instance context, - even though it seems logically implied by other constraints in the context. +T20666a.hs:11:10: error: [GHC-39999] + • Could not deduce ‘Eq (F [a])’ + arising from the superclasses of an instance declaration + from the context: D [a] + bound by the instance declaration at T20666a.hs:11:10-23 + Possible fix: + If the constraint looks soluble from a superclass of the instance context, + read 'Undecidable instances and loopy superclasses' in the user manual + • In the instance declaration for ‘C [a]’ diff --git a/testsuite/tests/typecheck/should_compile/T20666b.hs b/testsuite/tests/typecheck/should_fail/T20666b.hs similarity index 100% rename from testsuite/tests/typecheck/should_compile/T20666b.hs rename to testsuite/tests/typecheck/should_fail/T20666b.hs diff --git a/testsuite/tests/typecheck/should_fail/T20666b.stderr b/testsuite/tests/typecheck/should_fail/T20666b.stderr new file mode 100644 index 000000000000..9c0412248237 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T20666b.stderr @@ -0,0 +1,10 @@ + +T20666b.hs:11:10: error: [GHC-39999] + • Could not deduce ‘Eq (F [a])’ + arising from the superclasses of an instance declaration + from the context: D [a] + bound by the instance declaration at T20666b.hs:11:10-23 + Possible fix: + If the constraint looks soluble from a superclass of the instance context, + read 'Undecidable instances and loopy superclasses' in the user manual + • In the instance declaration for ‘C [a]’ diff --git a/testsuite/tests/typecheck/should_compile/T22891.hs b/testsuite/tests/typecheck/should_fail/T22891.hs similarity index 100% rename from testsuite/tests/typecheck/should_compile/T22891.hs rename to testsuite/tests/typecheck/should_fail/T22891.hs diff --git a/testsuite/tests/typecheck/should_fail/T22891.stderr b/testsuite/tests/typecheck/should_fail/T22891.stderr new file mode 100644 index 000000000000..ff4e71b7c982 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T22891.stderr @@ -0,0 +1,9 @@ + +T22891.hs:9:10: error: [GHC-39999] + • Could not deduce ‘Foo f’ + arising from the superclasses of an instance declaration + from the context: Bar f f + bound by the instance declaration at T22891.hs:9:10-31 + Possible fix: + add (Foo f) to the context of the instance declaration + • In the instance declaration for ‘Bar f (h k3)’ diff --git a/testsuite/tests/typecheck/should_compile/T22912.hs b/testsuite/tests/typecheck/should_fail/T22912.hs similarity index 100% rename from testsuite/tests/typecheck/should_compile/T22912.hs rename to testsuite/tests/typecheck/should_fail/T22912.hs diff --git a/testsuite/tests/typecheck/should_fail/T22912.stderr b/testsuite/tests/typecheck/should_fail/T22912.stderr new file mode 100644 index 000000000000..b0885eae2a0a --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T22912.stderr @@ -0,0 +1,20 @@ + +T22912.hs:17:16: error: [GHC-39999] + • Could not deduce ‘Implies c’ + arising from the head of a quantified constraint + arising from a use of ‘go’ + from the context: Exactly (Implies c) + bound by a quantified context at T22912.hs:17:16-17 + Possible fix: + add (Implies c) to the context of + the type signature for: + anythingDict :: forall (c :: Constraint). Dict c + or If the constraint looks soluble from a superclass of the instance context, + read 'Undecidable instances and loopy superclasses' in the user manual + • In the expression: go + In an equation for ‘anythingDict’: + anythingDict + = go + where + go :: (Exactly (Implies c) => Implies c) => Dict c + go = Dict diff --git a/testsuite/tests/typecheck/should_fail/T6161.stderr b/testsuite/tests/typecheck/should_fail/T6161.stderr index f9a9a9e1e19d..71c7455abd7d 100644 --- a/testsuite/tests/typecheck/should_fail/T6161.stderr +++ b/testsuite/tests/typecheck/should_fail/T6161.stderr @@ -1,10 +1,7 @@ -T6161.hs:19:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Super (Fam a)’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Super (Fam a)’ to the instance context, - even though it seems logically implied by other constraints in the context. +T6161.hs:19:10: error: [GHC-39999] + • Could not deduce ‘Super (Fam a)’ + arising from the superclasses of an instance declaration + from the context: Foo a + bound by the instance declaration at T6161.hs:19:10-31 + • In the instance declaration for ‘Duper (Fam a)’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 2651fd1dfc08..19f331f35773 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -241,7 +241,7 @@ test('tcfail215', normal, compile_fail, ['']) test('tcfail216', normal, compile_fail, ['']) test('tcfail217', normal, compile_fail, ['']) test('tcfail218', normal, compile_fail, ['']) -test('tcfail223', normal, compile, ['']) # To become compile_fail after migration period (see #22912) +test('tcfail223', normal, compile_fail, ['']) test('tcfail224', normal, compile_fail, ['']) test('tcfail225', normal, compile_fail, ['']) @@ -293,7 +293,7 @@ test('T19187a', normal, compile_fail, ['']) test('T2534', normal, compile_fail, ['']) test('T7175', normal, compile_fail, ['']) test('T7210', normal, compile_fail, ['']) -test('T6161', normal, compile, ['']) # To become compile_fail after migration period (see #22912) +test('T6161', normal, compile_fail, ['']) test('T7368', normal, compile_fail, ['']) test('T7264', normal, compile_fail, ['']) test('T6069', normal, compile_fail, ['']) @@ -668,8 +668,11 @@ test('T21530a', normal, compile_fail, ['']) test('T21530b', normal, compile_fail, ['']) test('T22570', normal, compile_fail, ['']) test('T22645', normal, compile_fail, ['']) -test('T20666', normal, compile, ['']) # To become compile_fail after migration period (see #22912) -test('T20666a', normal, compile, ['']) # To become compile_fail after migration period (see #22912) +test('T20666', normal, compile_fail, ['']) +test('T20666a', normal, compile_fail, ['']) +test('T20666b', normal, compile_fail, ['']) +test('T22891', normal, compile_fail, ['']) +test('T22912', normal, compile_fail, ['']) test('T22924a', normal, compile_fail, ['']) test('T22924b', normal, compile_fail, ['']) test('T22940', normal, compile_fail, ['']) diff --git a/testsuite/tests/typecheck/should_fail/tcfail223.stderr b/testsuite/tests/typecheck/should_fail/tcfail223.stderr index 2ccfd00dda6b..d3173adde735 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail223.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail223.stderr @@ -1,10 +1,9 @@ -tcfail223.hs:10:10: warning: [GHC-36038] [-Wloopy-superclass-solve (in -Wdefault)] - I am solving the constraint ‘Class1 a’, - arising from the superclasses of an instance declaration, - in a way that might turn out to loop at runtime. - Starting from GHC 9.10, this warning will turn into an error. - See the user manual, § Undecidable instances and loopy superclasses. - Suggested fix: - Add the constraint ‘Class1 a’ to the instance context, - even though it seems logically implied by other constraints in the context. +tcfail223.hs:10:10: error: [GHC-39999] + • Could not deduce ‘Class1 a’ + arising from the superclasses of an instance declaration + from the context: Class3 a + bound by the instance declaration at tcfail223.hs:10:10-29 + Possible fix: + add (Class1 a) to the context of the instance declaration + • In the instance declaration for ‘Class2 a’ -- GitLab