Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
395e0ad1
by sheaf at 2025-04-16T12:33:26-04:00
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:
... | ... | @@ -170,7 +170,6 @@ Library |
170 | 170 | , GHC.Exception
|
171 | 171 | , GHC.Exception.Type
|
172 | 172 | , GHC.ExecutionStack
|
173 | - , GHC.ExecutionStack.Internal
|
|
174 | 173 | , GHC.Exts
|
175 | 174 | , GHC.Fingerprint
|
176 | 175 | , GHC.Fingerprint.Type
|
... | ... | @@ -247,9 +246,7 @@ Library |
247 | 246 | , GHC.TopHandler
|
248 | 247 | , GHC.TypeError
|
249 | 248 | , GHC.TypeLits
|
250 | - , GHC.TypeLits.Internal
|
|
251 | 249 | , GHC.TypeNats
|
252 | - , GHC.TypeNats.Internal
|
|
253 | 250 | , GHC.Unicode
|
254 | 251 | , GHC.Weak
|
255 | 252 | , GHC.Weak.Finalize
|
... | ... | @@ -17,6 +17,10 @@ |
17 | 17 | * `Control.Concurrent.threadWaitWriteSTM`
|
18 | 18 | * `System.Timeout.timeout`
|
19 | 19 | * `GHC.Conc.Signal.runHandlers`
|
20 | + * The following internal modules have been removed from `base`, as per [CLC #217](https://github.com/haskell/core-libraries-committee/issues/217):
|
|
21 | + * `GHC.TypeLits.Internal`
|
|
22 | + * `GHC.TypeNats.Internal`
|
|
23 | + * `GHC.ExecutionStack.Internal`.
|
|
20 | 24 | |
21 | 25 | ## 4.21.0.0 *TBA*
|
22 | 26 | * Change `SrcLoc` to be a strict and unboxed (finishing [CLC proposal #55](https://github.com/haskell/core-libraries-committee/issues/55))
|
1 | --- |
|
|
2 | --- Module : GHC.Internal.ExecutionStack.Internal
|
|
3 | --- Copyright : (c) The University of Glasgow 2013-2015
|
|
4 | --- License : see libraries/base/LICENSE
|
|
5 | ---
|
|
6 | --- Maintainer : ghc-devs@haskell.org
|
|
7 | --- Stability : internal
|
|
8 | --- Portability : non-portable (GHC Extensions)
|
|
9 | ---
|
|
10 | --- Internals of the "GHC.ExecutionStack" module.
|
|
11 | ---
|
|
12 | --- /The API of this module is unstable and not meant to be consumed by the general public./
|
|
13 | --- If you absolutely must depend on it, make sure to use a tight upper
|
|
14 | --- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
|
|
15 | --- change rapidly without much warning.
|
|
16 | ---
|
|
17 | --- @since 4.9.0.0
|
|
18 | - |
|
19 | -module GHC.ExecutionStack.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (
|
|
20 | - -- * Internal
|
|
21 | - Location (..)
|
|
22 | - , SrcLoc (..)
|
|
23 | - , StackTrace
|
|
24 | - , stackFrames
|
|
25 | - , stackDepth
|
|
26 | - , collectStackTrace
|
|
27 | - , showStackFrames
|
|
28 | - , invalidateDebugCache
|
|
29 | - ) where
|
|
30 | - |
|
31 | -import GHC.Internal.ExecutionStack.Internal |
1 | -{-# LANGUAGE Safe #-}
|
|
2 | -{-# OPTIONS_HADDOCK not-home #-}
|
|
3 | - |
|
4 | --- |
|
|
5 | ---
|
|
6 | --- Module : GHC.TypeLits.Internal
|
|
7 | --- Copyright : (c) The University of Glasgow, 1994-2000
|
|
8 | --- License : see libraries/base/LICENSE
|
|
9 | ---
|
|
10 | --- Maintainer : ghc-devs@haskell.org
|
|
11 | --- Stability : internal
|
|
12 | --- Portability : non-portable (GHC extensions)
|
|
13 | ---
|
|
14 | --- __Do not use this module.__ Use "GHC.TypeLits" instead.
|
|
15 | ---
|
|
16 | --- This module is internal-only and was exposed by accident. It may be
|
|
17 | --- removed without warning in a future version.
|
|
18 | ---
|
|
19 | --- /The API of this module is unstable and is tightly coupled to GHC's internals./
|
|
20 | --- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather
|
|
21 | --- than @base < 5@, because the interface can change rapidly without much warning.
|
|
22 | ---
|
|
23 | --- The technical reason for this module's existence is that it is needed
|
|
24 | --- to prevent module cycles while still allowing these identifiers to be
|
|
25 | --- imported in "Data.Type.Ord".
|
|
26 | ---
|
|
27 | --- @since 4.16.0.0
|
|
28 | - |
|
29 | -module GHC.TypeLits.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-}
|
|
30 | - (Symbol,
|
|
31 | - CmpSymbol,
|
|
32 | - CmpChar
|
|
33 | - ) where
|
|
34 | - |
|
35 | -import GHC.Internal.TypeLits.Internal |
1 | -{-# LANGUAGE Safe #-}
|
|
2 | -{-# OPTIONS_HADDOCK not-home #-}
|
|
3 | - |
|
4 | -module GHC.TypeNats.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-}
|
|
5 | - (Natural,
|
|
6 | - CmpNat
|
|
7 | - ) where
|
|
8 | - |
|
9 | -import GHC.Internal.TypeNats.Internal |
... | ... | @@ -5365,20 +5365,6 @@ module GHC.ExecutionStack where |
5365 | 5365 | getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location])
|
5366 | 5366 | showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
5367 | 5367 | |
5368 | -module GHC.ExecutionStack.Internal where
|
|
5369 | - -- Safety: None
|
|
5370 | - type Location :: *
|
|
5371 | - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc}
|
|
5372 | - type SrcLoc :: *
|
|
5373 | - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int}
|
|
5374 | - type StackTrace :: *
|
|
5375 | - newtype StackTrace = ...
|
|
5376 | - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace)
|
|
5377 | - invalidateDebugCache :: GHC.Internal.Types.IO ()
|
|
5378 | - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS
|
|
5379 | - stackDepth :: StackTrace -> GHC.Internal.Types.Int
|
|
5380 | - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location]
|
|
5381 | - |
|
5382 | 5368 | module GHC.Exts where
|
5383 | 5369 | -- Safety: None
|
5384 | 5370 | (*#) :: Int# -> Int# -> Int#
|
... | ... | @@ -9672,15 +9658,6 @@ module GHC.TypeLits where |
9672 | 9658 | 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
|
9673 | 9659 | withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r
|
9674 | 9660 | |
9675 | -module GHC.TypeLits.Internal where
|
|
9676 | - -- Safety: Safe
|
|
9677 | - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering
|
|
9678 | - type family CmpChar a b
|
|
9679 | - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering
|
|
9680 | - type family CmpSymbol a b
|
|
9681 | - type Symbol :: *
|
|
9682 | - data Symbol
|
|
9683 | - |
|
9684 | 9661 | module GHC.TypeNats where
|
9685 | 9662 | -- Safety: Safe
|
9686 | 9663 | type (*) :: Natural -> Natural -> Natural
|
... | ... | @@ -9727,13 +9704,6 @@ module GHC.TypeNats where |
9727 | 9704 | withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r
|
9728 | 9705 | withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r
|
9729 | 9706 | |
9730 | -module GHC.TypeNats.Internal where
|
|
9731 | - -- Safety: Safe
|
|
9732 | - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering
|
|
9733 | - type family CmpNat a b
|
|
9734 | - type Natural :: *
|
|
9735 | - data Natural = ...
|
|
9736 | - |
|
9737 | 9707 | module GHC.Unicode where
|
9738 | 9708 | -- Safety: Safe
|
9739 | 9709 | type GeneralCategory :: *
|
... | ... | @@ -5337,20 +5337,6 @@ module GHC.ExecutionStack where |
5337 | 5337 | getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location])
|
5338 | 5338 | showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
5339 | 5339 | |
5340 | -module GHC.ExecutionStack.Internal where
|
|
5341 | - -- Safety: None
|
|
5342 | - type Location :: *
|
|
5343 | - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc}
|
|
5344 | - type SrcLoc :: *
|
|
5345 | - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int}
|
|
5346 | - type StackTrace :: *
|
|
5347 | - newtype StackTrace = ...
|
|
5348 | - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace)
|
|
5349 | - invalidateDebugCache :: GHC.Internal.Types.IO ()
|
|
5350 | - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS
|
|
5351 | - stackDepth :: StackTrace -> GHC.Internal.Types.Int
|
|
5352 | - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location]
|
|
5353 | - |
|
5354 | 5340 | module GHC.Exts where
|
5355 | 5341 | -- Safety: None
|
5356 | 5342 | (*#) :: Int# -> Int# -> Int#
|
... | ... | @@ -12718,15 +12704,6 @@ module GHC.TypeLits where |
12718 | 12704 | 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
|
12719 | 12705 | withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r
|
12720 | 12706 | |
12721 | -module GHC.TypeLits.Internal where
|
|
12722 | - -- Safety: Safe
|
|
12723 | - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering
|
|
12724 | - type family CmpChar a b
|
|
12725 | - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering
|
|
12726 | - type family CmpSymbol a b
|
|
12727 | - type Symbol :: *
|
|
12728 | - data Symbol
|
|
12729 | - |
|
12730 | 12707 | module GHC.TypeNats where
|
12731 | 12708 | -- Safety: Safe
|
12732 | 12709 | type (*) :: Natural -> Natural -> Natural
|
... | ... | @@ -12773,13 +12750,6 @@ module GHC.TypeNats where |
12773 | 12750 | withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r
|
12774 | 12751 | withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r
|
12775 | 12752 | |
12776 | -module GHC.TypeNats.Internal where
|
|
12777 | - -- Safety: Safe
|
|
12778 | - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering
|
|
12779 | - type family CmpNat a b
|
|
12780 | - type Natural :: *
|
|
12781 | - data Natural = ...
|
|
12782 | - |
|
12783 | 12753 | module GHC.Unicode where
|
12784 | 12754 | -- Safety: Safe
|
12785 | 12755 | type GeneralCategory :: *
|
... | ... | @@ -5505,20 +5505,6 @@ module GHC.ExecutionStack where |
5505 | 5505 | getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location])
|
5506 | 5506 | showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
5507 | 5507 | |
5508 | -module GHC.ExecutionStack.Internal where
|
|
5509 | - -- Safety: None
|
|
5510 | - type Location :: *
|
|
5511 | - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc}
|
|
5512 | - type SrcLoc :: *
|
|
5513 | - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int}
|
|
5514 | - type StackTrace :: *
|
|
5515 | - newtype StackTrace = ...
|
|
5516 | - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace)
|
|
5517 | - invalidateDebugCache :: GHC.Internal.Types.IO ()
|
|
5518 | - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS
|
|
5519 | - stackDepth :: StackTrace -> GHC.Internal.Types.Int
|
|
5520 | - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location]
|
|
5521 | - |
|
5522 | 5508 | module GHC.Exts where
|
5523 | 5509 | -- Safety: None
|
5524 | 5510 | (*#) :: Int# -> Int# -> Int#
|
... | ... | @@ -9890,15 +9876,6 @@ module GHC.TypeLits where |
9890 | 9876 | 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
|
9891 | 9877 | withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r
|
9892 | 9878 | |
9893 | -module GHC.TypeLits.Internal where
|
|
9894 | - -- Safety: Safe
|
|
9895 | - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering
|
|
9896 | - type family CmpChar a b
|
|
9897 | - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering
|
|
9898 | - type family CmpSymbol a b
|
|
9899 | - type Symbol :: *
|
|
9900 | - data Symbol
|
|
9901 | - |
|
9902 | 9879 | module GHC.TypeNats where
|
9903 | 9880 | -- Safety: Safe
|
9904 | 9881 | type (*) :: Natural -> Natural -> Natural
|
... | ... | @@ -9945,13 +9922,6 @@ module GHC.TypeNats where |
9945 | 9922 | withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r
|
9946 | 9923 | withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r
|
9947 | 9924 | |
9948 | -module GHC.TypeNats.Internal where
|
|
9949 | - -- Safety: Safe
|
|
9950 | - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering
|
|
9951 | - type family CmpNat a b
|
|
9952 | - type Natural :: *
|
|
9953 | - data Natural = ...
|
|
9954 | - |
|
9955 | 9925 | module GHC.Unicode where
|
9956 | 9926 | -- Safety: Safe
|
9957 | 9927 | type GeneralCategory :: *
|
... | ... | @@ -5365,20 +5365,6 @@ module GHC.ExecutionStack where |
5365 | 5365 | getStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe [Location])
|
5366 | 5366 | showStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
5367 | 5367 | |
5368 | -module GHC.ExecutionStack.Internal where
|
|
5369 | - -- Safety: None
|
|
5370 | - type Location :: *
|
|
5371 | - data Location = Location {objectName :: GHC.Internal.Base.String, functionName :: GHC.Internal.Base.String, srcLoc :: GHC.Internal.Maybe.Maybe SrcLoc}
|
|
5372 | - type SrcLoc :: *
|
|
5373 | - data SrcLoc = SrcLoc {sourceFile :: GHC.Internal.Base.String, sourceLine :: GHC.Internal.Types.Int, sourceColumn :: GHC.Internal.Types.Int}
|
|
5374 | - type StackTrace :: *
|
|
5375 | - newtype StackTrace = ...
|
|
5376 | - collectStackTrace :: GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe StackTrace)
|
|
5377 | - invalidateDebugCache :: GHC.Internal.Types.IO ()
|
|
5378 | - showStackFrames :: [Location] -> GHC.Internal.Show.ShowS
|
|
5379 | - stackDepth :: StackTrace -> GHC.Internal.Types.Int
|
|
5380 | - stackFrames :: StackTrace -> GHC.Internal.Maybe.Maybe [Location]
|
|
5381 | - |
|
5382 | 5368 | module GHC.Exts where
|
5383 | 5369 | -- Safety: None
|
5384 | 5370 | (*#) :: Int# -> Int# -> Int#
|
... | ... | @@ -9672,15 +9658,6 @@ module GHC.TypeLits where |
9672 | 9658 | 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
|
9673 | 9659 | withSomeSSymbol :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). GHC.Internal.Base.String -> (forall (s :: Symbol). SSymbol s -> r) -> r
|
9674 | 9660 | |
9675 | -module GHC.TypeLits.Internal where
|
|
9676 | - -- Safety: Safe
|
|
9677 | - type CmpChar :: GHC.Internal.Types.Char -> GHC.Internal.Types.Char -> GHC.Internal.Types.Ordering
|
|
9678 | - type family CmpChar a b
|
|
9679 | - type CmpSymbol :: Symbol -> Symbol -> GHC.Internal.Types.Ordering
|
|
9680 | - type family CmpSymbol a b
|
|
9681 | - type Symbol :: *
|
|
9682 | - data Symbol
|
|
9683 | - |
|
9684 | 9661 | module GHC.TypeNats where
|
9685 | 9662 | -- Safety: Safe
|
9686 | 9663 | type (*) :: Natural -> Natural -> Natural
|
... | ... | @@ -9727,13 +9704,6 @@ module GHC.TypeNats where |
9727 | 9704 | withKnownNat :: forall (n :: Nat) (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). SNat n -> (KnownNat n => r) -> r
|
9728 | 9705 | withSomeSNat :: forall (rep :: GHC.Internal.Types.RuntimeRep) (r :: TYPE rep). Natural -> (forall (n :: Nat). SNat n -> r) -> r
|
9729 | 9706 | |
9730 | -module GHC.TypeNats.Internal where
|
|
9731 | - -- Safety: Safe
|
|
9732 | - type CmpNat :: Natural -> Natural -> GHC.Internal.Types.Ordering
|
|
9733 | - type family CmpNat a b
|
|
9734 | - type Natural :: *
|
|
9735 | - data Natural = ...
|
|
9736 | - |
|
9737 | 9707 | module GHC.Unicode where
|
9738 | 9708 | -- Safety: Safe
|
9739 | 9709 | type GeneralCategory :: *
|