Simon Peyton Jones pushed to branch wip/T23162-part2 at Glasgow Haskell Compiler / GHC Commits: 71a84d13 by Simon Peyton Jones at 2025-12-08T13:17:58+00:00 Wibbles - - - - - 4 changed files: - compiler/GHC/Tc/Errors.hs - testsuite/tests/typecheck/should_fail/FunDepOrigin1b.stderr - testsuite/tests/typecheck/should_fail/T19415.stderr - testsuite/tests/typecheck/should_fail/T19415b.stderr Changes: ===================================== compiler/GHC/Tc/Errors.hs ===================================== @@ -652,13 +652,12 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics ] -- report2: we suppress these if there are insolubles elsewhere in the tree - report2 = [ ("Implicit params", is_ip, False, mkGroupReporter mkIPErr) - , ("Irreds", is_irred, False, mkGroupReporter mkIrredErr) + report2 = [ ("Irreds", is_irred, False, mkGroupReporter mkIrredErr) , ("Dicts", is_dict, False, mkGroupReporter mkDictErr) , ("Quantified", is_qc, False, mkGroupReporter mkQCErr) ] -- rigid_nom_eq, rigid_nom_tv_eq, - is_dict, is_equality, is_ip, is_FRR, is_irred :: ErrorItem -> Pred -> Bool + is_dict, is_equality, is_FRR, is_irred :: ErrorItem -> Pred -> Bool is_given_eq item pred | Given <- ei_flavour item @@ -716,9 +715,6 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics is_dict _ (ClassPred {}) = True is_dict _ _ = False - is_ip _ (ClassPred cls _) = isIPClass cls - is_ip _ _ = False - is_irred _ (IrredPred {}) = True is_irred _ _ = False @@ -1687,17 +1683,6 @@ givenConstraints ctxt ---------------- -mkIPErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport --- What would happen if an item is suppressed because of --- Note [Wanteds rewrite Wanteds: rewriter-sets] in GHC.Tc.Types.Constraint? --- Very unclear what's best. Let's not worry about this. -mkIPErr ctxt (item1:|others) - = do { (ctxt, binds, item1) <- relevantBindings True ctxt item1 - ; let msg = important ctxt $ UnboundImplicitParams (item1 :| others) - ; return $ add_relevant_bindings binds msg } - ----------------- - -- | Report a representation-polymorphism error to the user: -- a type is required to have a fixed runtime representation, -- but doesn't. @@ -2308,7 +2293,15 @@ mkQCErr ctxt items mkDictErr :: HasDebugCallStack => SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport -mkDictErr ctxt orig_items +-- Includes implict parameters +mkDictErr ctxt orig_items@(item1 :| others) + | ClassPred cls tys <- classifyPredType (errorItemPred item1) + , isIPClass cls -- Implicit parameters; no need to look in global instance envts + = do { (ctxt, binds, item1) <- relevantBindings True ctxt item1 + ; let msg = important ctxt $ UnboundImplicitParams (item1 :| others) + ; return $ add_relevant_bindings binds msg } + + | otherwise = do { inst_envs <- tcGetInstEnvs ; let min_items = elim_superclasses items lookups = map (lookup_cls_inst inst_envs) min_items @@ -2362,8 +2355,8 @@ mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped)) { (_, rel_binds, item) <- relevantBindings True ctxt item ; candidate_insts <- get_candidate_instances ; mb_noBuiltinInst_msg <- getNoBuiltinInstMsg item - ; return $ - CannotResolveInstance item unifiers candidate_insts rel_binds mb_noBuiltinInst_msg + ; return $ CannotResolveInstance item unifiers candidate_insts rel_binds + mb_noBuiltinInst_msg } -- Some matches => overlap errors ===================================== testsuite/tests/typecheck/should_fail/FunDepOrigin1b.stderr ===================================== @@ -1,12 +1,6 @@ - FunDepOrigin1b.hs:9:10: error: [GHC-39999] - • No instance for ‘C Bool (Maybe a0)’ arising from a use of ‘op’ + • No instance for ‘C Bool (Maybe a1)’ arising from a use of ‘op’ • In the expression: op True Nothing In the expression: (op True Nothing, op False []) In an equation for ‘foo’: foo _ = (op True Nothing, op False []) -FunDepOrigin1b.hs:9:27: error: [GHC-39999] - • No instance for ‘C Bool [a1]’ arising from a use of ‘op’ - • In the expression: op False [] - In the expression: (op True Nothing, op False []) - In an equation for ‘foo’: foo _ = (op True Nothing, op False []) ===================================== testsuite/tests/typecheck/should_fail/T19415.stderr ===================================== @@ -1,5 +1,5 @@ T19415.hs:27:8: error: [GHC-39999] - • No instance for ‘SetField "name" (Pet a0) (Pet b0) Char’ + • No instance for ‘SetField "name" (Pet a0) (Pet b) Char’ arising from a use of ‘setField’ • In the expression: setField @"name" 'c' (Pet "hi") In an equation for ‘loop’: loop = setField @"name" 'c' (Pet "hi") ===================================== testsuite/tests/typecheck/should_fail/T19415b.stderr ===================================== @@ -1,5 +1,5 @@ T19415b.hs:15:8: error: [GHC-39999] - • No instance for ‘Ping (T a0) (T b0) Char’ + • No instance for ‘Ping (T a0) (T b) Char’ arising from a use of ‘foo’ • In the expression: foo 'c' MkT In an equation for ‘loop’: loop = foo 'c' MkT View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71a84d133a0f7e42fe666d318d2c6678... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71a84d133a0f7e42fe666d318d2c6678... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)