Skip to content
Snippets Groups Projects
Unverified Commit dc2e9d2d authored by Krzysztof Gogolewski's avatar Krzysztof Gogolewski Committed by Zubin
Browse files

Use tcInferFRR to prevent bad generalisation

Fixes #23176

(cherry picked from commit 4b89bb54)
parent 734ad762
No related branches found
No related tags found
No related merge requests found
......@@ -1095,6 +1095,22 @@ Examples that might fail:
or multi-parameter type classes
- an inferred type that includes unboxed tuples
Note [Inferred type with escaping kind]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Check for an inferred type with an escaping kind; e.g. #23051
forall {k} {f :: k -> RuntimeRep} {g :: k} {a :: TYPE (f g)}. a
where the kind of the body of the forall mentions `f` and `g` which
are bound by the forall. No no no.
This check, mkInferredPolyId, is really in the wrong place:
`inferred_poly_ty` doesn't obey the PKTI and it would be better not to
generalise it in the first place; see #20686. But for now it works.
I considered adjusting the generalisation in GHC.Tc.Solver to directly check for
escaping kind variables; instead, promoting or defaulting them. But that
gets into the defaulting swamp and is a non-trivial and unforced
change, so I have left it alone for now.
Note [Impedance matching]
~~~~~~~~~~~~~~~~~~~~~~~~~
Consider
......@@ -1184,7 +1200,9 @@ tcMonoBinds is_rec sig_fn no_gen
, Nothing <- sig_fn name -- ...with no type signature
= setSrcSpanA b_loc $
do { ((co_fn, matches'), rhs_ty')
<- tcInfer $ \ exp_ty ->
<- tcInferFRR (FRRBinder name) $ \ exp_ty ->
-- tcInferFRR: the type of a let-binder must have
-- a fixed runtime rep. See #23176
tcExtendBinderStack [TcIdBndr_ExpType name exp_ty NotTopLevel] $
-- We extend the error context even for a non-recursive
-- function so that in type error messages we show the
......@@ -1206,7 +1224,9 @@ tcMonoBinds is_rec sig_fn no_gen
| NonRecursive <- is_rec -- ...binder isn't mentioned in RHS
, all (isNothing . sig_fn) bndrs
= addErrCtxt (patMonoBindsCtxt pat grhss) $
do { (grhss', pat_ty) <- tcInfer $ \ exp_ty ->
do { (grhss', pat_ty) <- tcInferFRR FRRPatBind $ \ exp_ty ->
-- tcInferFRR: the type of each let-binder must have
-- a fixed runtime rep. See #23176
tcGRHSsPat grhss exp_ty
; let exp_pat_ty :: Scaled ExpSigmaTypeFRR
......
T22743.hs:10:1: error:
• Quantified type's kind mentions quantified type variable
type: ‘forall {f :: * -> RuntimeRep} {g} {a :: TYPE (f g)}. a’
where the body of the forall has this kind: ‘TYPE (f g)’
• When checking the inferred type
x :: forall {f :: * -> RuntimeRep} {g} {a :: TYPE (f g)}. a
The binder ‘x’
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
T22743.hs:10:1: error:
The binder ‘x’
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
module T23176 where
import GHC.Exts
f = outOfScope :: (_ :: TYPE (r s))
(g :: _) = outOfScope :: (_ :: TYPE (r s))
T23176.hs:5:1: error:
The binder ‘f’
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
T23176.hs:5:1: error:
The binder ‘f’
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
T23176.hs:5:1: error:
The binder ‘f’
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
T23176.hs:6:1: error:
The pattern binding
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
T23176.hs:6:1: error:
The pattern binding
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
T23176.hs:6:1: error:
The pattern binding
cannot be assigned a fixed runtime representation, not even by defaulting.
Suggested fix: Add a type signature.
......@@ -113,3 +113,4 @@ test('RepPolyRule3', normal, compile_fail, ['']) ##
######################################################################
test('T23153', normal, compile_fail, [''])
test('T23154', normal, compile_fail, [''])
test('T23176', normal, compile_fail, ['-XPartialTypeSignatures -fdefer-out-of-scope-variables'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment