[Git][ghc/ghc][wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593] 2 commits: update comment
Patrick (@soulomoon)
gitlab at gitlab.haskell.org
Sun Jan 5 09:10:23 UTC 2025
Patrick pushed to branch wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593 at Glasgow Haskell Compiler / GHC
Commits:
6ff397a2 by Patrick at 2025-01-05T16:30:00+08:00
update comment
- - - - -
4c83df3b by Patrick at 2025-01-05T17:09:56+08:00
Change UnliftedNewtypesUnassociatedFamilyFail to UnliftedNewtypesUnassociatedFamilyInfer.
- - - - -
4 changed files:
- compiler/GHC/Tc/TyCl/Instance.hs
- + testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamilyInfer.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -945,10 +945,11 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity
-- Add constraints from the result signature
; res_kind <- tc_kind_sig m_ksig
- -- Do not add constraints from the data constructors
- -- See Note [Kind inference for data family instances]
-
-- Add constraints from the data constructors
+ -- Fix #25611
+ -- But becareful about the GADT style case,
+ -- do not unify LHS's kind with RHS's kind,
+ -- See Note [Kind inference for data family instances]
; kcConDecls new_or_data res_kind hs_cons
=====================================
testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamilyInfer.hs
=====================================
@@ -0,0 +1,29 @@
+{-# LANGUAGE UnliftedNewtypes #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE GADTs #-}
+
+module UnliftedNewtypesUnassociatedFamily where
+
+import GHC.Int (Int(I#))
+import GHC.Word (Word(W#))
+import GHC.Exts (Int#,Word#)
+import GHC.Exts (TYPE,RuntimeRep(IntRep,WordRep,TupleRep))
+
+data family DF :: TYPE (r :: RuntimeRep)
+
+-- it used to be failed: see #18891 and !4419
+-- See Note [Kind inference for data family instances]
+-- in GHC.Tc.TyCl.Instance
+-- but succ now see #25611
+newtype instance DF = MkDF1a Int#
+newtype instance DF = MkDF2a Word#
+newtype instance DF = MkDF3a (# Int#, Word# #)
+
+go = 1
+ where
+ x :: DF @IntRep
+ x = MkDF1a 3#
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -696,6 +696,7 @@ test('T505', normal, compile, [''])
test('T12928', normal, compile, [''])
test('UnliftedNewtypesGnd', normal, compile, [''])
test('UnliftedNewtypesUnassociatedFamily', normal, compile, [''])
+test('UnliftedNewtypesUnassociatedFamilyInfer', normal, compile, [''])
test('UnliftedNewtypesUnifySig', normal, compile, [''])
test('UnliftedNewtypesForall', normal, compile, [''])
test('UnlifNewUnify', normal, compile, [''])
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -552,7 +552,6 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, [''])
test('UnliftedNewtypesMismatchedKind', normal, compile_fail, [''])
test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, [''])
test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, [''])
-test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, [''])
test('T13834', normal, compile_fail, [''])
test('T17077', normal, compile_fail, [''])
test('T16512a', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef44934cc8de1b5ff84e63e8eaa3085c8620463f...4c83df3b0f784d27afcef9ccc28a9e3ef461f129
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef44934cc8de1b5ff84e63e8eaa3085c8620463f...4c83df3b0f784d27afcef9ccc28a9e3ef461f129
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/20250105/a05c92d5/attachment-0001.html>
More information about the ghc-commits
mailing list