[Git][ghc/ghc][master] Valid hole fits: don't suggest unsafeCoerce (#17940)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Sep 8 08:06:14 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
a0ccef7a by Krzysztof Gogolewski at 2023-09-08T04:05:42-04:00
Valid hole fits: don't suggest unsafeCoerce (#17940)
- - - - -
4 changed files:
- compiler/GHC/Tc/Errors/Hole.hs
- + testsuite/tests/typecheck/should_fail/T17940.hs
- + testsuite/tests/typecheck/should_fail/T17940.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/Errors/Hole.hs
=====================================
@@ -48,7 +48,7 @@ import GHC.Core.DataCon
import GHC.Core.Predicate( Pred(..), classifyPredType, eqRelRole )
import GHC.Types.Name
import GHC.Types.Name.Reader
-import GHC.Builtin.Names ( gHC_ERR )
+import GHC.Builtin.Names ( gHC_ERR, uNSAFE_COERCE )
import GHC.Types.Id
import GHC.Types.Var.Set
import GHC.Types.Var.Env
@@ -823,8 +823,8 @@ tcFilterHoleFits limit typed_hole ht@(hole_ty, _) candidates =
_ -> discard_it }
_ -> discard_it }
where
- -- We want to filter out undefined and the likes from GHC.Err
- not_trivial id = nameModule_maybe (idName id) /= Just gHC_ERR
+ -- We want to filter out undefined and the likes from GHC.Err (#17940)
+ not_trivial id = nameModule_maybe (idName id) `notElem` [Just gHC_ERR, Just uNSAFE_COERCE]
lookup :: HoleFitCandidate -> TcM (Maybe (Id, Type))
lookup (IdHFCand id) = return (Just (id, idType id))
=====================================
testsuite/tests/typecheck/should_fail/T17940.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE MagicHash #-}
+module T17940 where
+
+import GHC.Exts
+
+index# :: ByteArray# -> Int# -> Word8#
+index# a i = _ (indexWord8Array# a i)
=====================================
testsuite/tests/typecheck/should_fail/T17940.stderr
=====================================
@@ -0,0 +1,17 @@
+
+T17940.hs:7:14: error: [GHC-88464]
+ • Found hole: _ :: Word8# -> Word8#
+ • In the expression: _ (indexWord8Array# a i)
+ In an equation for ‘index#’: index# a i = _ (indexWord8Array# a i)
+ • Relevant bindings include
+ i :: Int# (bound at T17940.hs:7:10)
+ a :: ByteArray# (bound at T17940.hs:7:8)
+ index# :: ByteArray# -> Int# -> Word8# (bound at T17940.hs:7:1)
+ Valid hole fits include
+ notWord8# :: Word8# -> Word8#
+ (imported from ‘GHC.Exts’ at T17940.hs:4:1-15
+ (and originally defined in ‘GHC.Prim’))
+ coerce :: forall a b. Coercible a b => a -> b
+ with coerce @Word8# @Word8#
+ (imported from ‘GHC.Exts’ at T17940.hs:4:1-15
+ (and originally defined in ‘GHC.Prim’))
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -700,3 +700,4 @@ test('T22684', normal, compile_fail, [''])
test('T23514a', normal, compile_fail, [''])
test('T22478c', normal, compile_fail, [''])
test('T23776', normal, compile, ['']) # to become an error in GHC 9.12
+test('T17940', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0ccef7a44def216da92a0436249789c363a6f91
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0ccef7a44def216da92a0436249789c363a6f91
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/20230908/ae29ac8c/attachment-0001.html>
More information about the ghc-commits
mailing list