[Git][ghc/ghc][master] In mkDataConRep, ensure the in-scope set is right
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Feb 29 07:11:04 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00
In mkDataConRep, ensure the in-scope set is right
A small change that fixes #24489
- - - - -
3 changed files:
- compiler/GHC/Types/Id/Make.hs
- + testsuite/tests/deSugar/should_compile/T24489.hs
- testsuite/tests/deSugar/should_compile/all.T
Changes:
=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -946,8 +946,7 @@ mkDataConRep dc_bang_opts fam_envs wrap_name data_con
mk_boxer boxers = DCB (\ ty_args src_vars ->
do { let (ex_vars, term_vars) = splitAtList ex_tvs src_vars
subst1 = zipTvSubst univ_tvs ty_args
- subst2 = extendTCvSubstList subst1 ex_tvs
- (mkTyCoVarTys ex_vars)
+ subst2 = foldl2 extendTvSubstWithClone subst1 ex_tvs ex_vars
; (rep_ids, binds) <- go subst2 boxers term_vars
; return (ex_vars ++ rep_ids, binds) } )
=====================================
testsuite/tests/deSugar/should_compile/T24489.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE GADTs #-}
+module A where
+
+data Term where
+ BinaryTerm :: {-# UNPACK #-} !Bool -> tag -> Term
+
+f :: Term -> String
+f (BinaryTerm _ _) = "hello"
=====================================
testsuite/tests/deSugar/should_compile/all.T
=====================================
@@ -114,3 +114,4 @@ test('T19969', [grep_errmsg('LoopBreaker')], compile, ['-ddump-simpl -dsuppress-
test('T19883', normal, compile, [''])
test('T22719', normal, compile, ['-ddump-simpl -dsuppress-uniques -dno-typeable-binds'])
test('T23550', normal, compile, [''])
+test('T24489', normal, compile, ['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4cae4ecc8ab207c8180242b8fc062464fc70157
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4cae4ecc8ab207c8180242b8fc062464fc70157
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/20240229/1d0c2a6b/attachment-0001.html>
More information about the ghc-commits
mailing list