[Git][ghc/ghc][wip/T25647] add more tests
Patrick (@soulomoon)
gitlab at gitlab.haskell.org
Wed Feb 5 13:30:39 UTC 2025
Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC
Commits:
5dbae152 by Patrick at 2025-02-05T21:30:29+08:00
add more tests
- - - - -
3 changed files:
- testsuite/tests/typecheck/should_compile/T25647.hs → testsuite/tests/typecheck/should_compile/T25647a.hs
- + testsuite/tests/typecheck/should_compile/T25647b.hs
- testsuite/tests/typecheck/should_compile/all.T
Changes:
=====================================
testsuite/tests/typecheck/should_compile/T25647.hs → testsuite/tests/typecheck/should_compile/T25647a.hs
=====================================
@@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds, UnliftedNewtypes, TypeFamilies, PolyKinds, MagicHash #-}
-module T25647 where
+module T25647a where
import GHC.Exts
import Data.Kind
@@ -64,3 +64,9 @@ newtype instance Dix4 f where
data family Dix5 :: (k -> TYPE r) -> k
newtype instance Dix5 f = DIn5 (f (Dix5 f))
+-- -- newtype instance that is not TYPE 'LiftedRep
+-- data family Dix6 :: (k -> TYPE 'IntRep) -> k
+-- newtype instance Dix6 f where
+-- DIn6 :: forall ff. ff (Dix6 ff) -> Dix6 ff
+
+
=====================================
testsuite/tests/typecheck/should_compile/T25647b.hs
=====================================
@@ -0,0 +1,47 @@
+{-# LANGUAGE DataKinds, TypeFamilies, PolyKinds, MagicHash #-}
+
+module T25647b where
+
+import GHC.Exts
+import Data.Kind
+
+---------------------------
+-- without UnliftedNewtypes
+---------------------------
+
+-------------------- Plain newtypes -----------------
+
+-- A plain newtype, H98
+-- Defaulting happens; infers Fix1 :: forall k. (k -> Type) -> Type
+newtype Fix1a f = In1a (f (Fix1a f))
+
+-- A plain newtype, GADT syntax
+-- Defaulting happens; infers Fix1 :: forall k. (k -> Type) -> Type
+newtype Fix1b f where
+ In1b :: forall ff. ff (Fix1b ff) -> Fix1b ff
+
+
+-------------------- Data families with newtype instance -----------------
+
+-- data instance in GADT sytntax
+data family Dix1 :: (k -> Type) -> k
+data instance Dix1 f where
+ DIn1 :: forall ff. ff (Dix1 ff) -> Dix1 ff
+
+-- newtype instance in GADT syntax
+data family Dix2 :: (k -> Type) -> k
+newtype instance Dix2 f where
+ DIn2 :: forall ff. ff (Dix2 ff) -> Dix2 ff
+
+data family Dix2a :: (k -> Type) -> k
+newtype instance Dix2a f :: Type where
+ DIn2a :: forall ff. ff (Dix2a ff) -> Dix2a ff
+
+-- newtype instance in H98 syntax
+data family Dix3 :: (k -> Type) -> k
+newtype instance Dix3 f = DIn3 (f (Dix3 f))
+
+-- newtype instance in H98 syntax
+data family Dix5 :: (k -> TYPE r) -> k
+newtype instance Dix5 f = DIn5 (f (Dix5 f))
+
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -933,5 +933,6 @@ test('T25266', normal, compile, [''])
test('T25266a', normal, compile_fail, [''])
test('T25266b', normal, compile, [''])
test('T25597', normal, compile, [''])
-test('T25647', normal, compile, [''])
+test('T25647a', normal, compile, [''])
+test('T25647b', normal, compile, [''])
test('T25647_fail', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dbae152e0405b0ab8c195afa0ced469a0f01bf6
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dbae152e0405b0ab8c195afa0ced469a0f01bf6
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/20250205/f72a67f9/attachment-0001.html>
More information about the ghc-commits
mailing list