[Git][ghc/ghc][master] Enforce that bindings of implicit parameters are lifted
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Dec 29 20:37:36 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00
Enforce that bindings of implicit parameters are lifted
Fixes #24298
- - - - -
4 changed files:
- compiler/GHC/Tc/Gen/Bind.hs
- + testsuite/tests/typecheck/should_fail/T24298.hs
- + testsuite/tests/typecheck/should_fail/T24298.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/Gen/Bind.hs
=====================================
@@ -291,7 +291,7 @@ tcLocalBinds (HsIPBinds x (IPBinds _ ip_binds)) thing_inside
-- ?y = ?x + 1
tc_ip_bind :: Class -> IPBind GhcRn -> TcM (DictId, IPBind GhcTc)
tc_ip_bind ipClass (IPBind _ l_name@(L _ ip) expr)
- = do { ty <- newOpenFlexiTyVarTy
+ = do { ty <- newFlexiTyVarTy liftedTypeKind -- see #24298
; let p = mkStrLitTy $ hsIPNameFS ip
; ip_id <- newDict ipClass [ p, ty ]
; expr' <- tcCheckMonoExpr expr ty
=====================================
testsuite/tests/typecheck/should_fail/T24298.hs
=====================================
@@ -0,0 +1,4 @@
+{-# LANGUAGE ImplicitParams, MagicHash #-}
+module T24298 where
+
+f = let ?foo = 4# in True
=====================================
testsuite/tests/typecheck/should_fail/T24298.stderr
=====================================
@@ -0,0 +1,9 @@
+
+T24298.hs:4:16: error: [GHC-18872]
+ ⢠Couldn't match a lifted type with an unlifted type
+ When matching types
+ t0 :: *
+ GHC.Prim.Int# :: TYPE GHC.Types.IntRep
+ ⢠In the expression: 4#
+ In the expression: let ?foo = 4# in True
+ In an equation for âfâ: f = let ?foo = 4# in True
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -710,3 +710,4 @@ test('T23776', normal, compile_fail, ['']) # error due to -Werror=compat, schedu
test('T17940', normal, compile_fail, [''])
test('ErrorIndexLinks', normal, compile_fail, ['-fprint-error-index-links=always'])
test('T24064', normal, compile_fail, [''])
+test('T24298', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/685b467c690a79598526d904b599c183993b2d30
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/685b467c690a79598526d904b599c183993b2d30
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/20231229/65cf0b23/attachment-0001.html>
More information about the ghc-commits
mailing list