[Git][ghc/ghc][wip/data-kind] ghc-internal: Eliminate GHC.Internal.Data.Kind
Ben Gamari (@bgamari)
gitlab at gitlab.haskell.org
Thu Mar 7 14:06:35 UTC 2024
Ben Gamari pushed to branch wip/data-kind at Glasgow Haskell Compiler / GHC
Commits:
30f59e76 by Ben Gamari at 2024-03-07T09:06:24-05:00
ghc-internal: Eliminate GHC.Internal.Data.Kind
This was simply reexporting things from `ghc-prim`. Instead reexport
these directly from `Data.Kind`. Also add build ordering dependency to
work around #23942.
- - - - -
6 changed files:
- libraries/base/src/Data/Kind.hs
- libraries/ghc-internal/ghc-internal.cabal
- 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/Data/Kind.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
-- |
--
@@ -19,4 +19,6 @@ module Data.Kind
FUN
) where
-import GHC.Internal.Data.Kind
\ No newline at end of file
+import GHC.Num.BigNat () -- for build ordering (#23942)
+import GHC.Prim (FUN)
+import GHC.Types (Type, Constraint)
=====================================
libraries/ghc-internal/ghc-internal.cabal
=====================================
@@ -120,7 +120,6 @@ Library
GHC.Internal.Data.Functor.Utils
GHC.Internal.Data.IORef
GHC.Internal.Data.Ix
- GHC.Internal.Data.Kind
GHC.Internal.Data.List
GHC.Internal.Data.Maybe
GHC.Internal.Data.Monoid
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -1238,7 +1238,7 @@ module Data.Ix where
{-# MINIMAL range, (index | GHC.Internal.Ix.unsafeIndex), inRange #-}
module Data.Kind where
- -- Safety: Safe
+ -- Safety: Trustworthy
type Constraint :: *
type Constraint = GHC.Prim.CONSTRAINT GHC.Types.LiftedRep
type role FUN nominal representational representational
=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -1238,7 +1238,7 @@ module Data.Ix where
{-# MINIMAL range, (index | GHC.Internal.Ix.unsafeIndex), inRange #-}
module Data.Kind where
- -- Safety: Safe
+ -- Safety: Trustworthy
type Constraint :: *
type Constraint = GHC.Prim.CONSTRAINT GHC.Types.LiftedRep
type role FUN nominal representational representational
=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -1238,7 +1238,7 @@ module Data.Ix where
{-# MINIMAL range, (index | GHC.Internal.Ix.unsafeIndex), inRange #-}
module Data.Kind where
- -- Safety: Safe
+ -- Safety: Trustworthy
type Constraint :: *
type Constraint = GHC.Prim.CONSTRAINT GHC.Types.LiftedRep
type role FUN nominal representational representational
=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -1238,7 +1238,7 @@ module Data.Ix where
{-# MINIMAL range, (index | GHC.Internal.Ix.unsafeIndex), inRange #-}
module Data.Kind where
- -- Safety: Safe
+ -- Safety: Trustworthy
type Constraint :: *
type Constraint = GHC.Prim.CONSTRAINT GHC.Types.LiftedRep
type role FUN nominal representational representational
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30f59e76f6864b2ca02ea2ec5deb2fd93de06b0b
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30f59e76f6864b2ca02ea2ec5deb2fd93de06b0b
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/20240307/dac2ab0a/attachment-0001.html>
More information about the ghc-commits
mailing list