Hannes Siebenhandl pushed to branch wip/fendor/remove-deprecated-unstable-heap-representation-details at Glasgow Haskell Compiler / GHC

Commits:

8 changed files:

Changes:

  • libraries/base/src/GHC/Exts.hs
    ... ... @@ -26,12 +26,6 @@ module GHC.Exts
    26 26
          -- **  Legacy interface for arrays of arrays
    
    27 27
          module GHC.Internal.ArrayArray,
    
    28 28
          -- *  Primitive operations
    
    29
    -     {-# 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."] #-}
    
    30
    -     Prim.BCO,
    
    31
    -     {-# 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."] #-}
    
    32
    -     Prim.mkApUpd0#,
    
    33
    -     {-# 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."] #-}
    
    34
    -     Prim.newBCO#,
    
    35 29
          module GHC.Prim,
    
    36 30
          module GHC.Prim.Ext,
    
    37 31
          -- **  Running 'RealWorld' state thread
    
    ... ... @@ -131,9 +125,6 @@ import GHC.Prim hiding
    131 125
       , whereFrom#
    
    132 126
       , isByteArrayWeaklyPinned#, isMutableByteArrayWeaklyPinned#
    
    133 127
     
    
    134
    -  -- deprecated
    
    135
    -  , BCO, mkApUpd0#, newBCO#
    
    136
    -
    
    137 128
       -- Don't re-export vector FMA instructions
    
    138 129
       , fmaddFloatX4#
    
    139 130
       , fmsubFloatX4#
    
    ... ... @@ -256,8 +247,6 @@ import GHC.Prim hiding
    256 247
       , minWord8X32#
    
    257 248
       , minWord8X64#
    
    258 249
       )
    
    259
    -import qualified GHC.Prim as Prim
    
    260
    -  ( BCO, mkApUpd0#, newBCO# )
    
    261 250
     
    
    262 251
     import GHC.Prim.Ext
    
    263 252
     
    

  • libraries/ghci/GHCi/CreateBCO.hs
    ... ... @@ -6,10 +6,6 @@
    6 6
     {-# LANGUAGE UnboxedTuples #-}
    
    7 7
     {-# LANGUAGE RecordWildCards #-}
    
    8 8
     {-# LANGUAGE CPP #-}
    
    9
    -{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
    
    10
    --- TODO We want to import GHC.Internal.Base (BCO, mkApUpd0#, newBCO#) instead
    
    11
    --- of from GHC.Exts when we can require of the bootstrap compiler to have
    
    12
    --- ghc-internal.
    
    13 9
     
    
    14 10
     --
    
    15 11
     --  (c) The University of Glasgow 2002-2006
    
    ... ... @@ -30,7 +26,8 @@ import Data.Array.Base
    30 26
     import Foreign hiding (newArray)
    
    31 27
     import Unsafe.Coerce (unsafeCoerce)
    
    32 28
     import GHC.Arr          ( Array(..) )
    
    33
    -import GHC.Exts
    
    29
    +import GHC.Exts   hiding ( BCO, mkApUpd0#, newBCO# )
    
    30
    +import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# )
    
    34 31
     import GHC.IO
    
    35 32
     import Control.Exception ( ErrorCall(..) )
    
    36 33
     
    

  • libraries/ghci/GHCi/TH.hs
    1 1
     {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
    
    2 2
         TupleSections, RecordWildCards, InstanceSigs, CPP #-}
    
    3 3
     {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
    
    4
    -{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
    
    5
    --- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we
    
    6
    --- can require of the bootstrap compiler to have ghc-internal.
    
    7 4
     
    
    8 5
     -- |
    
    9 6
     -- Running TH splices
    
    ... ... @@ -112,7 +109,7 @@ import Data.IORef
    112 109
     import Data.Map (Map)
    
    113 110
     import qualified Data.Map as M
    
    114 111
     import Data.Maybe
    
    115
    -import GHC.Desugar (AnnotationWrapper(..))
    
    112
    +import GHC.Internal.Desugar (AnnotationWrapper(..))
    
    116 113
     import qualified GHC.Boot.TH.Syntax as TH
    
    117 114
     import Unsafe.Coerce
    
    118 115
     
    

  • libraries/ghci/ghci.cabal.in
    ... ... @@ -86,11 +86,7 @@ library
    86 86
             rts,
    
    87 87
             array            == 0.5.*,
    
    88 88
             base             >= 4.8 && < 4.23,
    
    89
    -        -- ghc-internal     == @ProjectVersionForLib@.*
    
    90
    -        -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from
    
    91
    -        -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH
    
    92
    -        -- and GHCi.CreateBCO when we require ghc-internal of the bootstrap
    
    93
    -        -- compiler
    
    89
    +        ghc-internal     >= 9.1001.0 && <=@ProjectVersionForLib@.0,
    
    94 90
             ghc-prim         >= 0.5.0 && < 0.14,
    
    95 91
             binary           == 0.8.*,
    
    96 92
             bytestring       >= 0.10 && < 0.13,
    

  • testsuite/tests/interface-stability/base-exports.stdout
    ... ... @@ -3221,8 +3221,6 @@ module GHC.Base where
    3221 3221
         {-# MINIMAL pure, ((<*>) | liftA2) #-}
    
    3222 3222
       type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType
    
    3223 3223
       data Array# a
    
    3224
    -  type BCO :: *
    
    3225
    -  data BCO
    
    3226 3224
       type Bool :: *
    
    3227 3225
       data Bool = False | True
    
    3228 3226
       type ByteArray# :: UnliftedType
    
    ... ... @@ -4115,7 +4113,6 @@ module GHC.Base where
    4115 4113
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    4116 4114
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    4117 4115
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    4118
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    4119 4116
       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 #)
    
    4120 4117
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    4121 4118
       modInt :: Int -> Int -> Int
    
    ... ... @@ -4174,7 +4171,6 @@ module GHC.Base where
    4174 4171
       negateInt8X64# :: Int8X64# -> Int8X64#
    
    4175 4172
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4176 4173
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    4177
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    4178 4174
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4179 4175
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    4180 4176
       newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #)
    
    ... ... @@ -5398,8 +5394,6 @@ module GHC.Exts where
    5398 5394
       data Array# a
    
    5399 5395
       type ArrayArray# :: UnliftedType
    
    5400 5396
       newtype ArrayArray# = ArrayArray# (Array# ByteArray#)
    
    5401
    -  type BCO :: *
    
    5402
    -  data BCO
    
    5403 5397
       type Bool :: *
    
    5404 5398
       data Bool = False | True
    
    5405 5399
       type ByteArray# :: UnliftedType
    
    ... ... @@ -6210,7 +6204,6 @@ module GHC.Exts where
    6210 6204
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    6211 6205
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    6212 6206
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    6213
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    6214 6207
       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 #)
    
    6215 6208
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    6216 6209
       mulIntMayOflo# :: Int# -> Int# -> Int#
    
    ... ... @@ -6262,7 +6255,6 @@ module GHC.Exts where
    6262 6255
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6263 6256
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    6264 6257
       newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #)
    
    6265
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    6266 6258
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6267 6259
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    6268 6260
       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
    3221 3221
         {-# MINIMAL pure, ((<*>) | liftA2) #-}
    
    3222 3222
       type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType
    
    3223 3223
       data Array# a
    
    3224
    -  type BCO :: *
    
    3225
    -  data BCO
    
    3226 3224
       type Bool :: *
    
    3227 3225
       data Bool = False | True
    
    3228 3226
       type ByteArray# :: UnliftedType
    
    ... ... @@ -4115,7 +4113,6 @@ module GHC.Base where
    4115 4113
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    4116 4114
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    4117 4115
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    4118
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    4119 4116
       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 #)
    
    4120 4117
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    4121 4118
       modInt :: Int -> Int -> Int
    
    ... ... @@ -4174,7 +4171,6 @@ module GHC.Base where
    4174 4171
       negateInt8X64# :: Int8X64# -> Int8X64#
    
    4175 4172
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4176 4173
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    4177
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    4178 4174
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4179 4175
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    4180 4176
       newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #)
    
    ... ... @@ -5370,8 +5366,6 @@ module GHC.Exts where
    5370 5366
       data Array# a
    
    5371 5367
       type ArrayArray# :: UnliftedType
    
    5372 5368
       newtype ArrayArray# = ArrayArray# (Array# ByteArray#)
    
    5373
    -  type BCO :: *
    
    5374
    -  data BCO
    
    5375 5369
       type Bool :: *
    
    5376 5370
       data Bool = False | True
    
    5377 5371
       type ByteArray# :: UnliftedType
    
    ... ... @@ -6182,7 +6176,6 @@ module GHC.Exts where
    6182 6176
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    6183 6177
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    6184 6178
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    6185
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    6186 6179
       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 #)
    
    6187 6180
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    6188 6181
       mulIntMayOflo# :: Int# -> Int# -> Int#
    
    ... ... @@ -6234,7 +6227,6 @@ module GHC.Exts where
    6234 6227
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6235 6228
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    6236 6229
       newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #)
    
    6237
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    6238 6230
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6239 6231
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    6240 6232
       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
    3221 3221
         {-# MINIMAL pure, ((<*>) | liftA2) #-}
    
    3222 3222
       type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType
    
    3223 3223
       data Array# a
    
    3224
    -  type BCO :: *
    
    3225
    -  data BCO
    
    3226 3224
       type Bool :: *
    
    3227 3225
       data Bool = False | True
    
    3228 3226
       type ByteArray# :: UnliftedType
    
    ... ... @@ -4118,7 +4116,6 @@ module GHC.Base where
    4118 4116
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    4119 4117
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    4120 4118
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    4121
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    4122 4119
       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 #)
    
    4123 4120
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    4124 4121
       modInt :: Int -> Int -> Int
    
    ... ... @@ -4177,7 +4174,6 @@ module GHC.Base where
    4177 4174
       negateInt8X64# :: Int8X64# -> Int8X64#
    
    4178 4175
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4179 4176
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    4180
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    4181 4177
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4182 4178
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    4183 4179
       newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #)
    
    ... ... @@ -5538,8 +5534,6 @@ module GHC.Exts where
    5538 5534
       data Array# a
    
    5539 5535
       type ArrayArray# :: UnliftedType
    
    5540 5536
       newtype ArrayArray# = ArrayArray# (Array# ByteArray#)
    
    5541
    -  type BCO :: *
    
    5542
    -  data BCO
    
    5543 5537
       type Bool :: *
    
    5544 5538
       data Bool = False | True
    
    5545 5539
       type ByteArray# :: UnliftedType
    
    ... ... @@ -6353,7 +6347,6 @@ module GHC.Exts where
    6353 6347
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    6354 6348
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    6355 6349
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    6356
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    6357 6350
       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 #)
    
    6358 6351
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    6359 6352
       mulIntMayOflo# :: Int# -> Int# -> Int#
    
    ... ... @@ -6405,7 +6398,6 @@ module GHC.Exts where
    6405 6398
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6406 6399
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    6407 6400
       newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #)
    
    6408
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    6409 6401
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6410 6402
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    6411 6403
       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
    3221 3221
         {-# MINIMAL pure, ((<*>) | liftA2) #-}
    
    3222 3222
       type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType
    
    3223 3223
       data Array# a
    
    3224
    -  type BCO :: *
    
    3225
    -  data BCO
    
    3226 3224
       type Bool :: *
    
    3227 3225
       data Bool = False | True
    
    3228 3226
       type ByteArray# :: UnliftedType
    
    ... ... @@ -4115,7 +4113,6 @@ module GHC.Base where
    4115 4113
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    4116 4114
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    4117 4115
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    4118
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    4119 4116
       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 #)
    
    4120 4117
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    4121 4118
       modInt :: Int -> Int -> Int
    
    ... ... @@ -4174,7 +4171,6 @@ module GHC.Base where
    4174 4171
       negateInt8X64# :: Int8X64# -> Int8X64#
    
    4175 4172
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4176 4173
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    4177
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    4178 4174
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    4179 4175
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    4180 4176
       newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #)
    
    ... ... @@ -5398,8 +5394,6 @@ module GHC.Exts where
    5398 5394
       data Array# a
    
    5399 5395
       type ArrayArray# :: UnliftedType
    
    5400 5396
       newtype ArrayArray# = ArrayArray# (Array# ByteArray#)
    
    5401
    -  type BCO :: *
    
    5402
    -  data BCO
    
    5403 5397
       type Bool :: *
    
    5404 5398
       data Bool = False | True
    
    5405 5399
       type ByteArray# :: UnliftedType
    
    ... ... @@ -6210,7 +6204,6 @@ module GHC.Exts where
    6210 6204
       minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
    
    6211 6205
       minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
    
    6212 6206
       minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
    
    6213
    -  mkApUpd0# :: forall a. BCO -> (# a #)
    
    6214 6207
       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 #)
    
    6215 6208
       mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    
    6216 6209
       mulIntMayOflo# :: Int# -> Int# -> Int#
    
    ... ... @@ -6262,7 +6255,6 @@ module GHC.Exts where
    6262 6255
       newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6263 6256
       newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
    
    6264 6257
       newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #)
    
    6265
    -  newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
    
    6266 6258
       newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
    
    6267 6259
       newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
    
    6268 6260
       newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #)