[Git][ghc/ghc][wip/soulomoon/25647-allow-newtype-instance-in-gadt-syntax] add test T25647

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Wed Feb 5 12:26:48 UTC 2025



Patrick pushed to branch wip/soulomoon/25647-allow-newtype-instance-in-gadt-syntax at Glasgow Haskell Compiler / GHC


Commits:
8ab05963 by Patrick at 2025-02-05T20:26:34+08:00
add test T25647

- - - - -


2 changed files:

- + testsuite/tests/indexed-types/should_compile/T25647.hs
- testsuite/tests/indexed-types/should_compile/all.T


Changes:

=====================================
testsuite/tests/indexed-types/should_compile/T25647.hs
=====================================
@@ -0,0 +1,73 @@
+{-# LANGUAGE DataKinds, UnliftedNewtypes, TypeFamilies, PolyKinds, MagicHash #-}
+
+module T25647 where
+
+import GHC.Exts
+import Data.Kind
+
+-------------------- 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
+
+-- A plain newtype, GADT syntax, with a return kind signature,
+-- and runtime-rep quantification in the data constructor
+-- Should infer Fix2 :: forall r k. (k -> TYPE r) -> TYPE r
+newtype Fix2 f :: TYPE r where
+   In2 :: forall r (ff :: TYPE r -> TYPE r). ff (Fix2 ff) -> Fix2 ff
+
+-- Plain newtype, H98 syntax, standalone kind signature
+-- Should get In3 :: forall r (f :: TYPE r -> TYPE r). Fix3 @r f -> Fix3 @r f
+type Fix3 :: forall r. (TYPE r -> TYPE r) -> TYPE r
+newtype Fix3 f = In3 (f (Fix3 f))
+
+-- Plain newtype, H98 syntax, standalone kind signature
+-- Should get In4 :: forall r k (f :: k -> TYPE r). Fix4 @r @k f -> Fix4 @r @k f
+type Fix4 :: forall r. (TYPE r -> TYPE r) -> TYPE r
+newtype Fix4 f where
+  In4 :: forall rr (ff :: TYPE rr -> TYPE rr).
+         ff (Fix4 ff) -> Fix4 @rr 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 GADT syntax
+-- The newtype instance defaults to LiftedRep
+-- fail with additional equality constraints:
+    -- • A newtype must not be a GADT:  [(t, LiftedRep), (r, LiftedRep),
+    --                                   (f, ff)]
+
+-- data family Dix4 :: (k -> TYPE r) -> k
+-- newtype instance Dix4 f where
+--   DIn4 :: forall ff. ff (Dix4 ff) -> Dix4 ff
+
+-- newtype instance in H98 syntax
+data family Dix5 :: (k -> TYPE r) -> k
+newtype instance Dix5 f = DIn5 (f (Dix5 f))
+
+data family Dix6 :: (k -> TYPE 'IntRep) -> k
+newtype instance Dix6 f where
+  DIn6 :: forall ff. ff (Dix6 ff) -> Dix6 ff


=====================================
testsuite/tests/indexed-types/should_compile/all.T
=====================================
@@ -315,3 +315,4 @@ test('T25611a', normal, compile, [''])
 test('T25611b', normal, compile, [''])
 test('T25611c', normal, compile, [''])
 test('T25611d', normal, compile, [''])
+test('T25647', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ab0596313559d7ca8eb2a15382a726aebae20c8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ab0596313559d7ca8eb2a15382a726aebae20c8
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/e194bb2e/attachment-0001.html>


More information about the ghc-commits mailing list