[Git][ghc/ghc][master] Use tcMkScaledFunTys in matchExpectedFunTys

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 624afa4a by sheaf at 2025-09-08T03:38:05-04:00 Use tcMkScaledFunTys in matchExpectedFunTys We should use tcMkScaledFunTys rather than mkScaledFunTys in GHC.Tc.Utils.Unify.matchExpectedFunTys, as the latter crashes when the kind of the result type is a bare metavariable. We know the result is always Type-like, so we don't need scaledFunTys to try to rediscover that from the kind. Fixes #26277 - - - - - 3 changed files: - compiler/GHC/Tc/Utils/Unify.hs - + testsuite/tests/typecheck/should_compile/T26277.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -804,9 +804,13 @@ matchExpectedFunTys herald _ctxt arity (Infer inf_res) thing_inside ; result <- thing_inside (map ExpFunPatTy arg_tys) res_ty ; arg_tys <- mapM (\(Scaled m t) -> Scaled m <$> readExpType t) arg_tys ; res_ty <- readExpType res_ty - -- NB: mkScaledFunTys arg_tys res_ty does not contain any foralls - -- (even nested ones), so no need to instantiate. - ; co <- fillInferResultNoInst (mkScaledFunTys arg_tys res_ty) inf_res + -- Remarks: + -- 1. use tcMkScaledFunTys rather than mkScaledFunTys, as we might + -- have res_ty :: kappa[tau] for a meta ty-var kappa, in which case + -- mkScaledFunTys would crash. See #26277. + -- 2. tcMkScaledFunTys arg_tys res_ty does not contain any foralls + -- (even nested ones), so no need to instantiate. + ; co <- fillInferResultNoInst (tcMkScaledFunTys arg_tys res_ty) inf_res ; return (mkWpCastN co, result) } matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside ===================================== testsuite/tests/typecheck/should_compile/T26277.hs ===================================== @@ -0,0 +1,13 @@ +module T26277 where + +import Data.Kind ( Type, Constraint ) +import GHC.Exts ( TYPE ) + +type FunLike :: forall {k}. (k -> k -> Type) -> Constraint +class FunLike p where + myId :: p a a +instance FunLike (->) where + myId x = x + +-- This caused a panic +test x = myId @(->) x ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -907,6 +907,7 @@ test('T22560e', normal, compile, ['']) test('T23514b', normal, compile, ['']) test('T23514c', normal, compile, ['']) test('T22537', normal, compile, ['']) +test('T26277', normal, compile, ['']) test('T18986a', normal, compile, ['']) test('T18986b', normal, compile, ['']) test('T23413', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/624afa4a65caa8ec23f85e70574dfb60... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/624afa4a65caa8ec23f85e70574dfb60... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)