[Git][ghc/ghc][wip/T23153] Show an error when we cannot default a concrete tyvar
Krzysztof Gogolewski (@monoidal)
gitlab at gitlab.haskell.org
Wed Mar 22 18:58:30 UTC 2023
Krzysztof Gogolewski pushed to branch wip/T23153 at Glasgow Haskell Compiler / GHC
Commits:
c318ddb7 by Krzysztof Gogolewski at 2023-03-22T19:58:06+01:00
Show an error when we cannot default a concrete tyvar
Fixes #23153
- - - - -
7 changed files:
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Utils/Zonk.hs
- compiler/GHC/Types/Error/Codes.hs
- + testsuite/tests/rep-poly/T23153.hs
- + testsuite/tests/rep-poly/T23153.stderr
- testsuite/tests/rep-poly/all.T
Changes:
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1453,6 +1453,11 @@ instance Diagnostic TcRnMessage where
TcRnTyThingUsedWrong sort thing name
-> mkSimpleDecorated $
pprTyThingUsedWrong sort thing name
+ TcRnCannotDefaultConcrete frr
+ -> mkSimpleDecorated $
+ ppr (frr_context frr) $$
+ text "cannot be assigned a fixed runtime representation," <+>
+ text "not even by defaulting."
diagnosticReason = \case
TcRnUnknownMessage m
@@ -1931,6 +1936,8 @@ instance Diagnostic TcRnMessage where
-> ErrorWithoutFlag
TcRnTyThingUsedWrong{}
-> ErrorWithoutFlag
+ TcRnCannotDefaultConcrete{}
+ -> ErrorWithoutFlag
diagnosticHints = \case
TcRnUnknownMessage m
@@ -2427,6 +2434,8 @@ instance Diagnostic TcRnMessage where
-> noHints
TcRnTyThingUsedWrong{}
-> noHints
+ TcRnCannotDefaultConcrete{}
+ -> [SuggestAddTypeSignatures UnnamedBinding]
diagnosticCode = constructorCode
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -3257,6 +3257,16 @@ data TcRnMessage where
-> !Name -- ^ Name of the thing used wrongly.
-> TcRnMessage
+ {- TcRnCannotDefaultConcrete is an error occurring when a concrete
+ type variable cannot be defaulted.
+
+ Test cases:
+ T23153
+ -}
+ TcRnCannotDefaultConcrete
+ :: !FixedRuntimeRepOrigin
+ -> TcRnMessage
+
deriving Generic
-- | Things forbidden in @type data@ declarations.
=====================================
compiler/GHC/Tc/Utils/Zonk.hs
=====================================
@@ -56,6 +56,7 @@ import GHC.Tc.Utils.TcType
import GHC.Tc.Utils.TcMType
import GHC.Tc.Utils.Env ( tcLookupGlobalOnly )
import GHC.Tc.Types.Evidence
+import GHC.Tc.Errors.Types
import GHC.Core.TyCo.Ppr ( pprTyVar )
import GHC.Core.TyCon
@@ -1810,6 +1811,9 @@ commitFlexi flexi tv zonked_kind
| isMultiplicityTy zonked_kind
-> do { traceTc "Defaulting flexi tyvar to Many:" (pprTyVar tv)
; return manyDataConTy }
+ | Just (ConcreteFRR origin) <- isConcreteTyVar_maybe tv
+ -> do { addErr $ TcRnCannotDefaultConcrete origin
+ ; return (anyTypeOfKind zonked_kind) }
| otherwise
-> do { traceTc "Defaulting flexi tyvar to Any:" (pprTyVar tv)
; return (anyTypeOfKind zonked_kind) }
=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -539,6 +539,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnBadlyStaged" = 28914
GhcDiagnosticCode "TcRnStageRestriction" = 18157
GhcDiagnosticCode "TcRnTyThingUsedWrong" = 10969
+ GhcDiagnosticCode "TcRnCannotDefaultConcrete" = 52083
-- IllegalNewtypeReason
GhcDiagnosticCode "DoesNotHaveSingleField" = 23517
=====================================
testsuite/tests/rep-poly/T23153.hs
=====================================
@@ -0,0 +1,8 @@
+module T23153 where
+
+import GHC.Exts
+
+f :: forall r s (a :: TYPE (r s)). a -> ()
+f = f
+
+g h = f (h ())
=====================================
testsuite/tests/rep-poly/T23153.stderr
=====================================
@@ -0,0 +1,15 @@
+
+T23153.hs:8:1: error: [GHC-52083]
+ The argument ‘(h ())’ of ‘f’
+ cannot be assigned a fixed runtime representation, not even by defaulting.
+ Suggested fix: Add a type signature.
+
+T23153.hs:8:1: error: [GHC-52083]
+ The argument ‘(h ())’ of ‘f’
+ cannot be assigned a fixed runtime representation, not even by defaulting.
+ Suggested fix: Add a type signature.
+
+T23153.hs:8:1: error: [GHC-52083]
+ The argument ‘(h ())’ of ‘f’
+ cannot be assigned a fixed runtime representation, not even by defaulting.
+ Suggested fix: Add a type signature.
=====================================
testsuite/tests/rep-poly/all.T
=====================================
@@ -116,3 +116,4 @@ test('T21650_b', normal, compile_fail, ['-Wno-deprecated-flags']) ##
test('T23051', normal, compile_fail, [''])
+test('T23153', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c318ddb78ff7276c5721f26a530116ccd370be72
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c318ddb78ff7276c5721f26a530116ccd370be72
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230322/e4d2ab10/attachment-0001.html>
More information about the ghc-commits
mailing list