Hannes Siebenhandl pushed to branch wip/fendor/remove-deprecated-unstable-heap-representation-details at Glasgow Haskell Compiler / GHC Commits: 46f9b063 by fendor at 2025-07-23T18:59:26+02:00 Remove deprecated functions from the ghci package - - - - - 070008a4 by fendor at 2025-07-23T18:59:26+02:00 base: Remove unstable heap representation details from GHC.Exts - - - - - 8 changed files: - libraries/base/src/GHC/Exts.hs - libraries/ghci/GHCi/CreateBCO.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/ghci.cabal.in - 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/Exts.hs ===================================== @@ -26,12 +26,6 @@ module GHC.Exts -- ** Legacy interface for arrays of arrays module GHC.Internal.ArrayArray, -- * Primitive operations - {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-} - Prim.BCO, - {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-} - Prim.mkApUpd0#, - {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-} - Prim.newBCO#, module GHC.Prim, module GHC.Prim.Ext, -- ** Running 'RealWorld' state thread @@ -131,9 +125,6 @@ import GHC.Prim hiding , whereFrom# , isByteArrayWeaklyPinned#, isMutableByteArrayWeaklyPinned# - -- deprecated - , BCO, mkApUpd0#, newBCO# - -- Don't re-export vector FMA instructions , fmaddFloatX4# , fmsubFloatX4# @@ -256,8 +247,6 @@ import GHC.Prim hiding , minWord8X32# , minWord8X64# ) -import qualified GHC.Prim as Prim - ( BCO, mkApUpd0#, newBCO# ) import GHC.Prim.Ext ===================================== libraries/ghci/GHCi/CreateBCO.hs ===================================== @@ -6,10 +6,6 @@ {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE CPP #-} -{-# OPTIONS_GHC -Wno-warnings-deprecations #-} --- TODO We want to import GHC.Internal.Base (BCO, mkApUpd0#, newBCO#) instead --- of from GHC.Exts when we can require of the bootstrap compiler to have --- ghc-internal. -- -- (c) The University of Glasgow 2002-2006 @@ -30,7 +26,8 @@ import Data.Array.Base import Foreign hiding (newArray) import Unsafe.Coerce (unsafeCoerce) import GHC.Arr ( Array(..) ) -import GHC.Exts +import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# ) +import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# ) import GHC.IO import Control.Exception ( ErrorCall(..) ) ===================================== libraries/ghci/GHCi/TH.hs ===================================== @@ -1,9 +1,6 @@ {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric, TupleSections, RecordWildCards, InstanceSigs, CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} -{-# OPTIONS_GHC -Wno-warnings-deprecations #-} --- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we --- can require of the bootstrap compiler to have ghc-internal. -- | -- Running TH splices @@ -112,7 +109,7 @@ import Data.IORef import Data.Map (Map) import qualified Data.Map as M import Data.Maybe -import GHC.Desugar (AnnotationWrapper(..)) +import GHC.Internal.Desugar (AnnotationWrapper(..)) import qualified GHC.Boot.TH.Syntax as TH import Unsafe.Coerce ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -86,11 +86,7 @@ library rts, array == 0.5.*, base >= 4.8 && < 4.23, - -- ghc-internal == @ProjectVersionForLib@.* - -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from - -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH - -- and GHCi.CreateBCO when we require ghc-internal of the bootstrap - -- compiler + ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0, ghc-prim >= 0.5.0 && < 0.14, binary == 0.8.*, bytestring >= 0.10 && < 0.13, ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -3221,8 +3221,6 @@ module GHC.Base where {-# MINIMAL pure, ((<*>) | liftA2) #-} type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType data Array# a - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -4115,7 +4113,6 @@ module GHC.Base where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) modInt :: Int -> Int -> Int @@ -4174,7 +4171,6 @@ module GHC.Base where negateInt8X64# :: Int8X64# -> Int8X64# newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) @@ -5398,8 +5394,6 @@ module GHC.Exts where data Array# a type ArrayArray# :: UnliftedType newtype ArrayArray# = ArrayArray# (Array# ByteArray#) - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -6210,7 +6204,6 @@ module GHC.Exts where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) mulIntMayOflo# :: Int# -> Int# -> Int# @@ -6262,7 +6255,6 @@ module GHC.Exts where newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -3221,8 +3221,6 @@ module GHC.Base where {-# MINIMAL pure, ((<*>) | liftA2) #-} type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType data Array# a - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -4115,7 +4113,6 @@ module GHC.Base where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) modInt :: Int -> Int -> Int @@ -4174,7 +4171,6 @@ module GHC.Base where negateInt8X64# :: Int8X64# -> Int8X64# newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) @@ -5370,8 +5366,6 @@ module GHC.Exts where data Array# a type ArrayArray# :: UnliftedType newtype ArrayArray# = ArrayArray# (Array# ByteArray#) - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -6182,7 +6176,6 @@ module GHC.Exts where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) mulIntMayOflo# :: Int# -> Int# -> Int# @@ -6234,7 +6227,6 @@ module GHC.Exts where newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -3221,8 +3221,6 @@ module GHC.Base where {-# MINIMAL pure, ((<*>) | liftA2) #-} type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType data Array# a - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -4118,7 +4116,6 @@ module GHC.Base where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) modInt :: Int -> Int -> Int @@ -4177,7 +4174,6 @@ module GHC.Base where negateInt8X64# :: Int8X64# -> Int8X64# newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) @@ -5538,8 +5534,6 @@ module GHC.Exts where data Array# a type ArrayArray# :: UnliftedType newtype ArrayArray# = ArrayArray# (Array# ByteArray#) - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -6353,7 +6347,6 @@ module GHC.Exts where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) mulIntMayOflo# :: Int# -> Int# -> Int# @@ -6405,7 +6398,6 @@ module GHC.Exts where newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -3221,8 +3221,6 @@ module GHC.Base where {-# MINIMAL pure, ((<*>) | liftA2) #-} type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType data Array# a - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -4115,7 +4113,6 @@ module GHC.Base where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) modInt :: Int -> Int -> Int @@ -4174,7 +4171,6 @@ module GHC.Base where negateInt8X64# :: Int8X64# -> Int8X64# newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) @@ -5398,8 +5394,6 @@ module GHC.Exts where data Array# a type ArrayArray# :: UnliftedType newtype ArrayArray# = ArrayArray# (Array# ByteArray#) - type BCO :: * - data BCO type Bool :: * data Bool = False | True type ByteArray# :: UnliftedType @@ -6210,7 +6204,6 @@ module GHC.Exts where minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# - mkApUpd0# :: forall a. BCO -> (# a #) mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) mulIntMayOflo# :: Int# -> Int# -> Int# @@ -6262,7 +6255,6 @@ module GHC.Exts where newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #) - newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7b4788c6dcb8801126f0ad4b2ce864f... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7b4788c6dcb8801126f0ad4b2ce864f... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Hannes Siebenhandl (@fendor)