[Git][ghc/ghc][wip/T26255] Further improvements

Simon Peyton Jones pushed to branch wip/T26255 at Glasgow Haskell Compiler / GHC Commits: e2f7ce2c by Simon Peyton Jones at 2025-08-23T17:52:38+01:00 Further improvements * Suppress all Wanted superclass constraints * Priorities (F tys ~ rigid) over custom type errors - - - - - 3 changed files: - compiler/GHC/Tc/Errors.hs - + testsuite/tests/typecheck/should_fail/T26255c.hs - + testsuite/tests/typecheck/should_fail/T26255c.stderr Changes: ===================================== compiler/GHC/Tc/Errors.hs ===================================== @@ -50,6 +50,8 @@ import GHC.Types.Name.Env import GHC.Types.SrcLoc import GHC.Types.Basic import GHC.Types.Error +import GHC.Types.Unique( hasKey ) +import GHC.Builtin.Names( errorMessageTypeErrorFamKey ) import qualified GHC.Types.Unique.Map as UM import GHC.Unit.Module @@ -439,10 +441,10 @@ reportBadTelescope _ _ skol_info skols -- See Note [Constraints to ignore]. ignoreConstraint :: Ct -> Bool ignoreConstraint ct - | AssocFamPatOrigin <- ctOrigin ct - = True - | otherwise - = False + = case ctOrigin ct of + AssocFamPatOrigin -> True -- See (CIG1) + WantedSuperclassOrigin {} -> True -- See (CIG2) + _ -> False -- | Makes an error item from a constraint, calculating whether or not -- the item should be suppressed. See Note [Wanteds rewrite Wanteds] @@ -612,14 +614,14 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics , ("skolem eq2", skolem_eq, True, mkSkolReporter) -- Next, family applications like (F t1 t2 ~ rigid_ty) - -- These can be solved by doing a type-family reduction for F + -- These could be solved by doing a type-family reduction for F -- which probably means fixing a unfication variable in t1/t2 -- See discussion in #26255, where F had an injectivity annotation, -- and we had [W] F alpha ~ "foo" -- The real error is that the "foo" should be "bar", because there is -- type instance F Int = "bar" - -- We could additionally filter on the injectivty annotation, but - -- currenlty we don't. + -- We could additionally filter on the injectivty annotation, + -- but currently we don't. , ("fam app", is_fam_app_eq, True, mkGroupReporter mkEqErr) -- Put custom type errors after solid equality errors. In #26255 we @@ -680,8 +682,11 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics is_FRR item _ = isJust $ fixedRuntimeRepOrigin_maybe item -- Things like (F t1 t2 ~N Maybe s) - is_fam_app_eq _ (EqPred NomEq ty1 ty2) = isJust (isSatTyFamApp ty1) && isRigidTy ty2 - is_fam_app_eq _ _ = False + -- But only proper type families; not (TypeError t1 t2 ~N blah) + is_fam_app_eq _ (EqPred NomEq ty1 ty2) + | Just (tc,_) <- isSatTyFamApp ty1 + = not (tc `hasKey` errorMessageTypeErrorFamKey) && isRigidTy ty2 + is_fam_app_eq _ _ = False -- Things like (a ~N b) or (a ~N F Bool) skolem_eq _ (EqPred NomEq ty1 _) = isSkolemTy tc_lvl ty1 @@ -819,7 +824,7 @@ they will remain unfilled, and might have been used to rewrite another constrain Currently, the constraints to ignore are: -1) Constraints generated in order to unify associated type instance parameters +(CIG1) Constraints generated in order to unify associated type instance parameters with class parameters. Here are two illustrative examples: class C (a :: k) where @@ -847,6 +852,10 @@ Currently, the constraints to ignore are: If there is any trouble, checkValidFamInst bleats, aborting compilation. +(CIG2) Superclasses of Wanteds. These are generated on in case they trigger functional + dependencies. If such a constraint is unsolved, then its "parent" constraint must + also be unsolved, and is much more informative to the user (#26255). + Note [Implementation of Unsatisfiable constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The Unsatisfiable constraint was introduced in GHC proposal #433 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0433-un...). ===================================== testsuite/tests/typecheck/should_fail/T26255c.hs ===================================== @@ -0,0 +1,30 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableSuperClasses #-} + +module T26255c where + +import Data.Kind +import Data.Proxy +import GHC.TypeLits + +type MinVersion = 1 + +class + ( KnownNat (ProtVerLow era) + , MinVersion <= ProtVerLow era + ) => + Era era + where + type ProtVerLow era :: Nat + +newtype EraFamily era = EraFamily Int + +class Era era => NewEra era where + eraFamilySize :: EraFamily era -> Int + +printEraFamilySize :: EraFamily era -> IO () +printEraFamilySize = print . eraFamilySize ===================================== testsuite/tests/typecheck/should_fail/T26255c.stderr ===================================== @@ -0,0 +1,11 @@ +T26255c.hs:30:30: error: [GHC-39999] + • No instance for ‘NewEra era’ + arising from a use of ‘eraFamilySize’ + Possible fix: + add (NewEra era) to the context of + the type signature for: + printEraFamilySize :: forall {k} (era :: k). EraFamily era -> IO () + • In the second argument of ‘(.)’, namely ‘eraFamilySize’ + In the expression: print . eraFamilySize + In an equation for ‘printEraFamilySize’: + printEraFamilySize = print . eraFamilySize View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e2f7ce2cfeb3cd60798dfb7feb9c2b1a... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e2f7ce2cfeb3cd60798dfb7feb9c2b1a... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)