[Git][ghc/ghc][wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593] add test to ensure kind specialization is working as Note [Kind inference for...

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Sat Jan 4 17:39:50 UTC 2025



Patrick pushed to branch wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593 at Glasgow Haskell Compiler / GHC


Commits:
888319b8 by Patrick at 2025-01-05T01:39:36+08:00
add test to ensure kind specialization is working as Note [Kind inference for data family instances]

- - - - -


2 changed files:

- + testsuite/tests/typecheck/should_compile/InstanceConKindSpecializationDataFamily.hs
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
testsuite/tests/typecheck/should_compile/InstanceConKindSpecializationDataFamily.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+-- {-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE GADTs #-}
+
+module InstanceConKindSpecializationDataFamily where
+
+import GHC.Prim (Int#)
+
+-- | A data family with a kind signature
+data family T :: forall k. (k->v) -> k -> v
+-- ensure the kind specialization is correctly handled in the gadt style data instance
+-- see Note [Kind inference for data family instances]
+data instance T p q where
+      MkkT :: forall r. r Int -> T r Int
+      MkkV :: forall l. l Int# -> T l Int#


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -932,3 +932,4 @@ test('T25266', normal, compile, [''])
 test('T25266a', normal, compile_fail, [''])
 test('T25266b', normal, compile, [''])
 test('T25597', normal, compile, [''])
+test('InstanceConKindSpecializationDataFamily', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/888319b875a81796cfa9fff4d8d0cd62b386a185

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/888319b875a81796cfa9fff4d8d0cd62b386a185
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/20250104/2b140509/attachment-0001.html>


More information about the ghc-commits mailing list