[Git][ghc/ghc][wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593] Update Note [Implementation of UnliftedNewtypes]

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Sun Jan 5 04:01:29 UTC 2025



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


Commits:
f81233c6 by Patrick at 2025-01-05T12:01:13+08:00
Update Note [Implementation of UnliftedNewtypes]

- - - - -


1 changed file:

- compiler/GHC/Tc/TyCl.hs


Changes:

=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -2423,7 +2423,7 @@ There are also some changes for dealing with families:
    UnliftedNewtypes is on. This allows us to write things like:
      data family Foo :: TYPE 'IntRep
 
-2. In a newtype instance (with -XUnliftedNewtypes), if the user does
+2. In a newtype instance, if the user does
    not write a kind signature, we want to allow the possibility that
    the kind is not Type, so we use newOpenTypeKind instead of liftedTypeKind.
    This is done in tcDataFamInstHeader in GHC.Tc.TyCl.Instance. Example:
@@ -2463,7 +2463,16 @@ If we expect the argument to MkA to have kind Type, then we get a kind-mismatch
 error. The problem is that there is no way to connect this mismatch error to
 -XUnliftedNewtypes, and suggest enabling the extension. So, instead, we allow
 the A to type-check, but then find the problem when doing validity checking (and
-where we get make a suitable error message). One potential worry is
+where we get make a suitable error message).
+
+The same handling, is done for newtype data instances, resolving #25593.
+So the following example would be suggested to enable UnliftedNewtypes:
+
+  -- no UnliftedNewtypes
+  data family D :: UnliftedType
+  newtype instance D = MkD Any
+
+One potential worry is
 
   {-# LANGUAGE PolyKinds #-}
   newtype B a = MkB a
@@ -2482,16 +2491,6 @@ the validity checker), that will not happen. But I cannot think of a non-contriv
 example that will notice this lack of inference, so it seems better to improve
 error messages than be able to infer this instantiation.
 
-Another place to imrpove the error messages with the same handling is in the case
-of a newtype instance,
-
-  -- no UnliftedNewtypes
-
-  data family D :: UnliftedType
-  newtype instance D = MkD Any
-
-Here we also want to be suggesting to enable UnliftedNewtypes. So we allow the
-possibility that the kind is not Type regardless of whether UnliftedNewtypes is enabled.
 
 Note [Implementation of UnliftedDatatypes]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~



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

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


More information about the ghc-commits mailing list