Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
624afa4a
by sheaf at 2025-09-08T03:38:05-04:00
3 changed files:
- compiler/GHC/Tc/Utils/Unify.hs
- + testsuite/tests/typecheck/should_compile/T26277.hs
- testsuite/tests/typecheck/should_compile/all.T
Changes:
... | ... | @@ -804,9 +804,13 @@ matchExpectedFunTys herald _ctxt arity (Infer inf_res) thing_inside |
804 | 804 | ; result <- thing_inside (map ExpFunPatTy arg_tys) res_ty
|
805 | 805 | ; arg_tys <- mapM (\(Scaled m t) -> Scaled m <$> readExpType t) arg_tys
|
806 | 806 | ; res_ty <- readExpType res_ty
|
807 | - -- NB: mkScaledFunTys arg_tys res_ty does not contain any foralls
|
|
808 | - -- (even nested ones), so no need to instantiate.
|
|
809 | - ; co <- fillInferResultNoInst (mkScaledFunTys arg_tys res_ty) inf_res
|
|
807 | + -- Remarks:
|
|
808 | + -- 1. use tcMkScaledFunTys rather than mkScaledFunTys, as we might
|
|
809 | + -- have res_ty :: kappa[tau] for a meta ty-var kappa, in which case
|
|
810 | + -- mkScaledFunTys would crash. See #26277.
|
|
811 | + -- 2. tcMkScaledFunTys arg_tys res_ty does not contain any foralls
|
|
812 | + -- (even nested ones), so no need to instantiate.
|
|
813 | + ; co <- fillInferResultNoInst (tcMkScaledFunTys arg_tys res_ty) inf_res
|
|
810 | 814 | ; return (mkWpCastN co, result) }
|
811 | 815 | |
812 | 816 | matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
|
1 | +module T26277 where
|
|
2 | + |
|
3 | +import Data.Kind ( Type, Constraint )
|
|
4 | +import GHC.Exts ( TYPE )
|
|
5 | + |
|
6 | +type FunLike :: forall {k}. (k -> k -> Type) -> Constraint
|
|
7 | +class FunLike p where
|
|
8 | + myId :: p a a
|
|
9 | +instance FunLike (->) where
|
|
10 | + myId x = x
|
|
11 | + |
|
12 | +-- This caused a panic
|
|
13 | +test x = myId @(->) x |
... | ... | @@ -907,6 +907,7 @@ test('T22560e', normal, compile, ['']) |
907 | 907 | test('T23514b', normal, compile, [''])
|
908 | 908 | test('T23514c', normal, compile, [''])
|
909 | 909 | test('T22537', normal, compile, [''])
|
910 | +test('T26277', normal, compile, [''])
|
|
910 | 911 | test('T18986a', normal, compile, [''])
|
911 | 912 | test('T18986b', normal, compile, [''])
|
912 | 913 | test('T23413', normal, compile, [''])
|