
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 395e0ad1 by sheaf at 2025-04-16T12:33:26-04:00 base: remove .Internal modules (e.g. GHC.TypeLits) This commit removes the following internal modules from base, as per CLC proposal 217: - GHC.TypeNats.Internal - GHC.TypeLits.Internal - GHC.ExecutionStack.Internal Fixes #25007 - - - - - 9 changed files: - libraries/base/base.cabal.in - libraries/base/changelog.md - − libraries/base/src/GHC/ExecutionStack/Internal.hs - − libraries/base/src/GHC/TypeLits/Internal.hs - − libraries/base/src/GHC/TypeNats/Internal.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/base.cabal.in ===================================== @@ -170,7 +170,6 @@ Library , GHC.Exception , GHC.Exception.Type , GHC.ExecutionStack - , GHC.ExecutionStack.Internal , GHC.Exts , GHC.Fingerprint , GHC.Fingerprint.Type @@ -247,9 +246,7 @@ Library , GHC.TopHandler , GHC.TypeError , GHC.TypeLits - , GHC.TypeLits.Internal , GHC.TypeNats - , GHC.TypeNats.Internal , GHC.Unicode , GHC.Weak , GHC.Weak.Finalize ===================================== libraries/base/changelog.md ===================================== @@ -17,6 +17,10 @@ * `Control.Concurrent.threadWaitWriteSTM` * `System.Timeout.timeout` * `GHC.Conc.Signal.runHandlers` + * The following internal modules have been removed from `base`, as per [CLC #217](https://github.com/haskell/core-libraries-committee/issues/217): + * `GHC.TypeLits.Internal` + * `GHC.TypeNats.Internal` + * `GHC.ExecutionStack.Internal`. ## 4.21.0.0 *TBA* * Change `SrcLoc` to be a strict and unboxed (finishing [CLC proposal #55](https://github.com/haskell/core-libraries-committee/issues/55)) ===================================== libraries/base/src/GHC/ExecutionStack/Internal.hs deleted ===================================== @@ -1,31 +0,0 @@ --- | --- Module : GHC.Internal.ExecutionStack.Internal --- Copyright : (c) The University of Glasgow 2013-2015 --- License : see libraries/base/LICENSE --- --- Maintainer : ghc-devs@haskell.org --- Stability : internal --- Portability : non-portable (GHC Extensions) --- --- Internals of the "GHC.ExecutionStack" module. --- --- /The API of this module is unstable and not meant to be consumed by the general public./ --- If you absolutely must depend on it, make sure to use a tight upper --- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can --- change rapidly without much warning. --- --- @since 4.9.0.0 - -module GHC.ExecutionStack.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} ( - -- * Internal - Location (..) - , SrcLoc (..) - , StackTrace - , stackFrames - , stackDepth - , collectStackTrace - , showStackFrames - , invalidateDebugCache - ) where - -import GHC.Internal.ExecutionStack.Internal ===================================== libraries/base/src/GHC/TypeLits/Internal.hs deleted ===================================== @@ -1,35 +0,0 @@ -{-# LANGUAGE Safe #-} -{-# OPTIONS_HADDOCK not-home #-} - --- | --- --- Module : GHC.TypeLits.Internal --- Copyright : (c) The University of Glasgow, 1994-2000 --- License : see libraries/base/LICENSE --- --- Maintainer : ghc-devs@haskell.org --- Stability : internal --- Portability : non-portable (GHC extensions) --- --- __Do not use this module.__ Use "GHC.TypeLits" instead. --- --- This module is internal-only and was exposed by accident. It may be --- removed without warning in a future version. --- --- /The API of this module is unstable and is tightly coupled to GHC's internals./ --- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather --- than @base < 5@, because the interface can change rapidly without much warning. --- --- The technical reason for this module's existence is that it is needed --- to prevent module cycles while still allowing these identifiers to be --- imported in "Data.Type.Ord". --- --- @since 4.16.0.0 - -module GHC.TypeLits.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} - (Symbol, - CmpSymbol, - CmpChar - ) where - -import GHC.Internal.TypeLits.Internal ===================================== libraries/base/src/GHC/TypeNats/Internal.hs deleted ===================================== @@ -1,9 +0,0 @@ -{-# LANGUAGE Safe #-} -{-# OPTIONS_HADDOCK not-home #-} - -module GHC.TypeNats.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} - (Natural, - CmpNat - ) where - -import GHC.Internal.TypeNats.Internal ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -5365,20 +5365,6 @@ module GHC.ExecutionStack where getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location]) showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String) -module GHC.ExecutionStack.Internal where - -- Safety: None - type Location :: * - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc} - type SrcLoc :: * - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int} - type StackTrace :: * - newtype StackTrace = ... - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace) - invalidateDebugCache :: GHC.Internal.Types.IO () - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS - stackDepth :: StackTrace -> GHC.Internal.Types.Int - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location] - module GHC.Exts where -- Safety: None (*#) :: Int# -> Int# -> Int# @@ -9672,15 +9658,6 @@ module GHC.TypeLits where withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Bignum.Integer.Integer -> (forall (n :: Nat). GHC.Internal.Maybe.Maybe (SNat n) -> r) -> r withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r -module GHC.TypeLits.Internal where - -- Safety: Safe - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering - type family CmpChar a b - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering - type family CmpSymbol a b - type Symbol :: * - data Symbol - module GHC.TypeNats where -- Safety: Safe type (*) :: Natural -> Natural -> Natural @@ -9727,13 +9704,6 @@ module GHC.TypeNats where withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r -module GHC.TypeNats.Internal where - -- Safety: Safe - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering - type family CmpNat a b - type Natural :: * - data Natural = ... - module GHC.Unicode where -- Safety: Safe type GeneralCategory :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -5337,20 +5337,6 @@ module GHC.ExecutionStack where getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location]) showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String) -module GHC.ExecutionStack.Internal where - -- Safety: None - type Location :: * - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc} - type SrcLoc :: * - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int} - type StackTrace :: * - newtype StackTrace = ... - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace) - invalidateDebugCache :: GHC.Internal.Types.IO () - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS - stackDepth :: StackTrace -> GHC.Internal.Types.Int - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location] - module GHC.Exts where -- Safety: None (*#) :: Int# -> Int# -> Int# @@ -12718,15 +12704,6 @@ module GHC.TypeLits where withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Bignum.Integer.Integer -> (forall (n :: Nat). GHC.Internal.Maybe.Maybe (SNat n) -> r) -> r withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r -module GHC.TypeLits.Internal where - -- Safety: Safe - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering - type family CmpChar a b - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering - type family CmpSymbol a b - type Symbol :: * - data Symbol - module GHC.TypeNats where -- Safety: Safe type (*) :: Natural -> Natural -> Natural @@ -12773,13 +12750,6 @@ module GHC.TypeNats where withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r -module GHC.TypeNats.Internal where - -- Safety: Safe - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering - type family CmpNat a b - type Natural :: * - data Natural = ... - module GHC.Unicode where -- Safety: Safe type GeneralCategory :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -5505,20 +5505,6 @@ module GHC.ExecutionStack where getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location]) showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String) -module GHC.ExecutionStack.Internal where - -- Safety: None - type Location :: * - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc} - type SrcLoc :: * - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int} - type StackTrace :: * - newtype StackTrace = ... - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace) - invalidateDebugCache :: GHC.Internal.Types.IO () - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS - stackDepth :: StackTrace -> GHC.Internal.Types.Int - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location] - module GHC.Exts where -- Safety: None (*#) :: Int# -> Int# -> Int# @@ -9890,15 +9876,6 @@ module GHC.TypeLits where withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Bignum.Integer.Integer -> (forall (n :: Nat). GHC.Internal.Maybe.Maybe (SNat n) -> r) -> r withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r -module GHC.TypeLits.Internal where - -- Safety: Safe - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering - type family CmpChar a b - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering - type family CmpSymbol a b - type Symbol :: * - data Symbol - module GHC.TypeNats where -- Safety: Safe type (*) :: Natural -> Natural -> Natural @@ -9945,13 +9922,6 @@ module GHC.TypeNats where withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r -module GHC.TypeNats.Internal where - -- Safety: Safe - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering - type family CmpNat a b - type Natural :: * - data Natural = ... - module GHC.Unicode where -- Safety: Safe type GeneralCategory :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -5365,20 +5365,6 @@ module GHC.ExecutionStack where getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location]) showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String) -module GHC.ExecutionStack.Internal where - -- Safety: None - type Location :: * - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc} - type SrcLoc :: * - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int} - type StackTrace :: * - newtype StackTrace = ... - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace) - invalidateDebugCache :: GHC.Internal.Types.IO () - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS - stackDepth :: StackTrace -> GHC.Internal.Types.Int - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location] - module GHC.Exts where -- Safety: None (*#) :: Int# -> Int# -> Int# @@ -9672,15 +9658,6 @@ module GHC.TypeLits where withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Bignum.Integer.Integer -> (forall (n :: Nat). GHC.Internal.Maybe.Maybe (SNat n) -> r) -> r withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r -module GHC.TypeLits.Internal where - -- Safety: Safe - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering - type family CmpChar a b - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering - type family CmpSymbol a b - type Symbol :: * - data Symbol - module GHC.TypeNats where -- Safety: Safe type (*) :: Natural -> Natural -> Natural @@ -9727,13 +9704,6 @@ module GHC.TypeNats where withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r -module GHC.TypeNats.Internal where - -- Safety: Safe - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering - type family CmpNat a b - type Natural :: * - data Natural = ... - module GHC.Unicode where -- Safety: Safe type GeneralCategory :: * View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/395e0ad17c0d309637f079a05dbdc23e... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/395e0ad17c0d309637f079a05dbdc23e... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)