[Git][ghc/ghc][wip/amg/T22156] Mark GHC.Records as Trustworthy

Adam Gundry (@adamgundry) gitlab at gitlab.haskell.org
Wed Jan 10 08:21:04 UTC 2024



Adam Gundry pushed to branch wip/amg/T22156 at Glasgow Haskell Compiler / GHC


Commits:
c04fcaba by Adam Gundry at 2024-01-10T08:20:07+00:00
Mark GHC.Records as Trustworthy

The previous patch added an import of GHC.Exts, which means GHC.Records
ceases to be Safe-Inferred. Rather than breaking any user code which
relied on GHC.Records being considered Safe, we declare it Trustworthy.

- - - - -


5 changed files:

- libraries/base/src/GHC/Records.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
libraries/base/src/GHC/Records.hs
=====================================
@@ -3,6 +3,7 @@
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE Trustworthy #-}  -- See Note [GHC.Records is Trustworthy]
 
 -----------------------------------------------------------------------------
 -- |
@@ -26,7 +27,7 @@ module GHC.Records
        ) where
 
 import Data.Kind (Constraint)
-import GHC.Exts (TYPE)
+import GHC.Exts (TYPE) -- See Note [GHC.Records is Trustworthy]
 
 -- | Constraint representing the fact that the field @x@ belongs to
 -- the record type @r@ and has field type @a at .  This will be solved
@@ -42,3 +43,19 @@ type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> C
 class HasField x r a | x r -> a where
   -- | Selector function to extract the field from the record.
   getField :: r -> a
+
+
+{-
+Note [GHC.Records is Trustworthy]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+This module was originally inferred as Safe, because it defined a simple class
+that depended only upon the Prelude. However, when 'HasField' was generalised to
+support representation polymorphism, it became necessary to import 'TYPE' from
+"GHC.Exts", which is Unsafe.  By default this meant "GHC.Records" would have
+beeen inferred as Unsafe instead, which might break clients. Hence we mark
+"GHC.Records" as Trustworthy, so it can be used in Safe code.  It would be
+nice if we had a Trustworthy place from which to import 'TYPE', but that
+doesn't currently seem to exist.
+
+-}


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -9101,7 +9101,7 @@ module GHC.Real where
   underflowError :: forall a. a
 
 module GHC.Records where
-  -- Safety: Safe-Inferred
+  -- Safety: Trustworthy
   type HasField :: forall {k} {r_rep :: GHC.Types.RuntimeRep} {a_rep :: GHC.Types.RuntimeRep}. k -> TYPE r_rep -> TYPE a_rep -> Constraint
   class HasField x r a | x r -> a where
     getField :: r -> a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -11879,7 +11879,7 @@ module GHC.Real where
   underflowError :: forall a. a
 
 module GHC.Records where
-  -- Safety: Safe-Inferred
+  -- Safety: Trustworthy
   type HasField :: forall {k} {r_rep :: GHC.Types.RuntimeRep} {a_rep :: GHC.Types.RuntimeRep}. k -> TYPE r_rep -> TYPE a_rep -> Constraint
   class HasField x r a | x r -> a where
     getField :: r -> a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -9325,7 +9325,7 @@ module GHC.Real where
   underflowError :: forall a. a
 
 module GHC.Records where
-  -- Safety: Safe-Inferred
+  -- Safety: Trustworthy
   type HasField :: forall {k} {r_rep :: GHC.Types.RuntimeRep} {a_rep :: GHC.Types.RuntimeRep}. k -> TYPE r_rep -> TYPE a_rep -> Constraint
   class HasField x r a | x r -> a where
     getField :: r -> a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -9105,7 +9105,7 @@ module GHC.Real where
   underflowError :: forall a. a
 
 module GHC.Records where
-  -- Safety: Safe-Inferred
+  -- Safety: Trustworthy
   type HasField :: forall {k} {r_rep :: GHC.Types.RuntimeRep} {a_rep :: GHC.Types.RuntimeRep}. k -> TYPE r_rep -> TYPE a_rep -> Constraint
   class HasField x r a | x r -> a where
     getField :: r -> a



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c04fcaba8f7d9cc32c9a1506384e664dba880c62
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/20240110/615e2d43/attachment-0001.html>


More information about the ghc-commits mailing list