[Git][ghc/ghc][wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593] adding test case UnliftedNewtypesRunTypeRepPoly
Patrick (@soulomoon)
gitlab at gitlab.haskell.org
Wed Jan 8 15:29:26 UTC 2025
Patrick pushed to branch wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593 at Glasgow Haskell Compiler / GHC
Commits:
8997776e by Patrick at 2025-01-08T23:29:14+08:00
adding test case UnliftedNewtypesRunTypeRepPoly
- - - - -
2 changed files:
- + testsuite/tests/typecheck/should_compile/UnliftedNewtypesRunTypeRepPoly.hs
- testsuite/tests/typecheck/should_compile/all.T
Changes:
=====================================
testsuite/tests/typecheck/should_compile/UnliftedNewtypesRunTypeRepPoly.hs
=====================================
@@ -0,0 +1,32 @@
+{-# LANGUAGE GADTSyntax #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UnliftedNewtypes #-}
+{-# LANGUAGE RankNTypes #-}
+
+module UnliftedNewtypesRunTypeRepPoly where
+
+import GHC.Int (Int(I#))
+import GHC.Word (Word(W#))
+import GHC.Exts (Int#,Word#)
+import GHC.Types
+
+
+type N :: TYPE r -> TYPE r
+newtype N a = MkN a
+
+f :: Int# -> N Int#
+f x = MkN x
+
+g :: Int -> N Int
+g x = MkN x
+
+data family D :: Type -> k -> k
+newtype instance D Int a = MkD a
+
+f1 :: Int# -> D Int Int#
+f1 x = MkD x
+
+g1 :: Int -> D Int Int
+g1 x = MkD x
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -934,3 +934,4 @@ test('T25266a', normal, compile_fail, [''])
test('T25266b', normal, compile, [''])
test('T25597', normal, compile, [''])
test('InstanceConKindSpecializationDataFamily', normal, compile, [''])
+test('UnliftedNewtypesRunTypeRepPoly', normal, compile, [''])
\ No newline at end of file
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8997776ef9c9a52d2ac10b96460780f4850062b1
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8997776ef9c9a52d2ac10b96460780f4850062b1
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/20250108/367ac29a/attachment-0001.html>
More information about the ghc-commits
mailing list