recursion-ninja pushed to branch wip/fix-25636 at Glasgow Haskell Compiler / GHC

Commits:

14 changed files:

Changes:

  • compiler/GHC/Builtin/primops.txt.pp
    ... ... @@ -3937,9 +3937,9 @@ primop MkApUpd0_Op "mkApUpd0#" GenPrimOp
    3937 3937
        with
    
    3938 3938
        out_of_line = True
    
    3939 3939
     
    
    3940
    -primop  NewUDCOp "newUDC#" GenPrimOp
    
    3940
    +primop  NewNullaryClosureOp "newNullaryClosure#" GenPrimOp
    
    3941 3941
        Addr# -> State# s -> (# State# s, a #)
    
    3942
    -   { @newUDC#@ allocates a new application of an
    
    3942
    +   { @newNullaryClosure#@ allocates a new application of an
    
    3943 3943
          unlifted data constructor (identified by its info table). }
    
    3944 3944
        with
    
    3945 3945
        effect = ReadWriteEffect
    

  • compiler/GHC/ByteCode/Asm.hs
    ... ... @@ -107,7 +107,7 @@ bcoFreeNames bco
    107 107
     assembleBCOs
    
    108 108
       :: Profile
    
    109 109
       -> FlatBag (ProtoBCO Name)
    
    110
    -  -> FlatBag UnlinkedUDC
    
    110
    +  -> FlatBag UnlinkedNullaryClosure
    
    111 111
       -> [TyCon]
    
    112 112
       -> [(Name, ByteString)]
    
    113 113
       -> Maybe InternalModBreaks
    

  • compiler/GHC/ByteCode/Linker.hs
    ... ... @@ -59,7 +59,7 @@ linkBCO
    59 59
       -> PkgsLoaded
    
    60 60
       -> LinkerEnv
    
    61 61
       -> LinkedBreaks
    
    62
    -  -> NameEnv Int -- Named UDCs
    
    62
    +  -> NameEnv Int -- Named NullaryClosures
    
    63 63
       -> NameEnv Int -- Named BCOs
    
    64 64
       -> UnlinkedBCO
    
    65 65
       -> IO ResolvedBCO
    
    ... ... @@ -161,13 +161,13 @@ resolvePtr
    161 161
       -> PkgsLoaded
    
    162 162
       -> LinkerEnv
    
    163 163
       -> LinkedBreaks
    
    164
    -  -> NameEnv Int -- Named UDCs
    
    164
    +  -> NameEnv Int -- Named NullaryClosures
    
    165 165
       -> NameEnv Int -- Named BCOs
    
    166 166
       -> BCOPtr
    
    167 167
       -> IO ResolvedBCOPtr
    
    168 168
     resolvePtr interp pkgs_loaded le lb udc_ix bco_ix ptr = case ptr of
    
    169 169
       BCOPtrName nm
    
    170
    -    | Just ix <- lookupNameEnv udc_ix nm -- ref to another UDC in this group
    
    170
    +    | Just ix <- lookupNameEnv udc_ix nm -- ref to another NullaryClosure in this group
    
    171 171
         -> return (ResolvedBCORefUnlifted ix)
    
    172 172
     
    
    173 173
         | Just ix <- lookupNameEnv bco_ix nm -- ref to another BCO in this group
    

  • compiler/GHC/ByteCode/Types.hs
    ... ... @@ -16,7 +16,7 @@ module GHC.ByteCode.Types
    16 16
       , RegBitmap(..)
    
    17 17
       , NativeCallType(..), NativeCallInfo(..), voidTupleReturnInfo, voidPrimCallInfo
    
    18 18
       , ByteOff(..), WordOff(..), HalfWord(..)
    
    19
    -  , UnlinkedUDC(..)
    
    19
    +  , UnlinkedNullaryClosure(..)
    
    20 20
       , UnlinkedBCO(..), BCOPtr(..), BCONPtr(..)
    
    21 21
       , ItblEnv, ItblPtr(..)
    
    22 22
       , AddrEnv, AddrPtr(..)
    
    ... ... @@ -62,7 +62,7 @@ data CompiledByteCode = CompiledByteCode
    62 62
       { bc_bcos   :: FlatBag UnlinkedBCO
    
    63 63
         -- ^ Bunch of interpretable bindings
    
    64 64
     
    
    65
    -  , bc_udcs   :: FlatBag UnlinkedUDC
    
    65
    +  , bc_udcs   :: FlatBag UnlinkedNullaryClosure
    
    66 66
     
    
    67 67
       , bc_itbls  :: [(Name, ConInfoTable)]
    
    68 68
         -- ^ Mapping from DataCons to their info tables
    
    ... ... @@ -178,16 +178,16 @@ newtype AddrPtr = AddrPtr (RemotePtr ())
    178 178
     {- |
    
    179 179
     Named reference to an unlifted data constructor
    
    180 180
     -}
    
    181
    -data UnlinkedUDC
    
    182
    -   = UnlinkedUDC {
    
    183
    -       unlinkedUDCName :: !Name,
    
    184
    -       unlinkedUDCInfo :: !ConInfoTable
    
    181
    +data UnlinkedNullaryClosure
    
    182
    +   = UnlinkedNullaryClosure {
    
    183
    +       unlinkedNullaryClosureName :: !Name,
    
    184
    +       unlinkedNullaryClosureInfo :: !ConInfoTable
    
    185 185
        }
    
    186 186
     
    
    187
    -instance NFData UnlinkedUDC where
    
    188
    -  rnf UnlinkedUDC{..} =
    
    189
    -    rnf unlinkedUDCName `seq`
    
    190
    -    rnf unlinkedUDCInfo
    
    187
    +instance NFData UnlinkedNullaryClosure where
    
    188
    +  rnf UnlinkedNullaryClosure{..} =
    
    189
    +    rnf unlinkedNullaryClosureName `seq`
    
    190
    +    rnf unlinkedNullaryClosureInfo
    
    191 191
     
    
    192 192
     {-
    
    193 193
     --------------------------------------------------------------------------------
    

  • compiler/GHC/Linker/Loader.hs
    ... ... @@ -1019,21 +1019,21 @@ linkSomeBCOs :: Interp
    1019 1019
     
    
    1020 1020
     linkSomeBCOs interp pkgs_loaded le lb mods = foldr fun do_link mods []
    
    1021 1021
      where
    
    1022
    -  fun :: CompiledByteCode -> ([([UnlinkedUDC], [UnlinkedBCO])] -> t) -> [([UnlinkedUDC], [UnlinkedBCO])] -> t
    
    1022
    +  fun :: CompiledByteCode -> ([([UnlinkedNullaryClosure], [UnlinkedBCO])] -> t) -> [([UnlinkedNullaryClosure], [UnlinkedBCO])] -> t
    
    1023 1023
       fun CompiledByteCode{..} inner accum =
    
    1024 1024
         inner ((Foldable.toList bc_udcs, Foldable.toList bc_bcos) : accum)
    
    1025 1025
     
    
    1026
    -  do_link :: [([UnlinkedUDC], [UnlinkedBCO])] -> IO [(Name, HValueRef)]
    
    1026
    +  do_link :: [([UnlinkedNullaryClosure], [UnlinkedBCO])] -> IO [(Name, HValueRef)]
    
    1027 1027
       do_link [] = return []
    
    1028 1028
       do_link mods = do
    
    1029
    -    let flat_UDCs = [ udc | (udcs, _) <- mods, udc <- udcs ]
    
    1029
    +    let flat_NullaryClosures = [ udc | (udcs, _) <- mods, udc <- udcs ]
    
    1030 1030
             flat_BCOs = [ bco | (_, bcos) <- mods, bco <- bcos ]
    
    1031
    -        names_UDCs = map unlinkedUDCName flat_UDCs
    
    1031
    +        names_NullaryClosures = map unlinkedNullaryClosureName flat_NullaryClosures
    
    1032 1032
             names_BCOs = map unlinkedBCOName flat_BCOs
    
    1033 1033
             index_BCO = mkNameEnv (zip names_BCOs [0 ..])
    
    1034
    -        index_UDC = mkNameEnv (zip names_UDCs [length names_BCOs ..])
    
    1034
    +        index_NullaryClosure = mkNameEnv (zip names_NullaryClosures [length names_BCOs ..])
    
    1035 1035
     
    
    1036
    -    resolved_BCOs <- sequence [ linkBCO interp pkgs_loaded le lb index_UDC index_BCO bco | bco <- flat_BCOs ]
    
    1036
    +    resolved_BCOs <- sequence [ linkBCO interp pkgs_loaded le lb index_NullaryClosure index_BCO bco | bco <- flat_BCOs ]
    
    1037 1037
         hvrefs <- createBCOs interp resolved_BCOs
    
    1038 1038
         return (zip names_BCOs hvrefs)
    
    1039 1039
     
    

  • compiler/GHC/StgToByteCode.hs
    ... ... @@ -103,7 +103,7 @@ import Control.Monad.Trans.Reader (ReaderT(..))
    103 103
     import Control.Monad.Trans.State  (StateT(..))
    
    104 104
     import Data.Bifunctor (Bifunctor(..))
    
    105 105
     
    
    106
    -import GHCi.ResolvedBCO (ResolvedUDC(..))
    
    106
    +import GHCi.ResolvedBCO (ResolvedNullaryClosure(..))
    
    107 107
     
    
    108 108
     
    
    109 109
     -- -----------------------------------------------------------------------------
    
    ... ... @@ -310,7 +310,7 @@ argBits platform (rep : args)
    310 310
     
    
    311 311
     -- Compile code for the right-hand side of a top-level binding
    
    312 312
     
    
    313
    -schemeTopBind :: (Id, CgStgRhs) -> BcM (Either UnlinkedUDC (ProtoBCO Name))
    
    313
    +schemeTopBind :: (Id, CgStgRhs) -> BcM (Either UnlinkedNullaryClosure (ProtoBCO Name))
    
    314 314
     schemeTopBind (id, rhs)
    
    315 315
       | isUnliftedType (varType id), StgRhsCon _ dCon conNo _ _ _ <- rhs = do
    
    316 316
             profile <- getProfile
    
    ... ... @@ -334,8 +334,8 @@ schemeTopBind (id, rhs)
    334 334
                   Numbered i -> i
    
    335 335
                   NoNumber   -> 0 -- This defaulting seems unsafe?
    
    336 336
     
    
    337
    -            finalizer :: ConInfoTable -> Either UnlinkedUDC a
    
    338
    -            finalizer = Left . UnlinkedUDC (getName id)
    
    337
    +            finalizer :: ConInfoTable -> Either UnlinkedNullaryClosure a
    
    338
    +            finalizer = Left . UnlinkedNullaryClosure (getName id)
    
    339 339
     
    
    340 340
             pure . finalizer $ ConInfoTable
    
    341 341
                 tables_next_to_code
    

  • compiler/GHC/StgToCmm/Prim.hs
    ... ... @@ -1771,7 +1771,7 @@ emitPrimOp cfg primop =
    1771 1771
       DataToTagSmallOp -> alwaysExternal
    
    1772 1772
       DataToTagLargeOp -> alwaysExternal
    
    1773 1773
       MkApUpd0_Op -> alwaysExternal
    
    1774
    -  NewUDCOp -> alwaysExternal
    
    1774
    +  NewNullaryClosureOp -> alwaysExternal
    
    1775 1775
       NewBCOOp -> alwaysExternal
    
    1776 1776
       UnpackClosureOp -> alwaysExternal
    
    1777 1777
       ListThreadsOp -> alwaysExternal
    

  • compiler/GHC/StgToJS/Prim.hs
    ... ... @@ -1164,7 +1164,7 @@ genPrim prof bound ty op = case op of
    1164 1164
       GetSparkOp                        -> unhandledPrimop op
    
    1165 1165
       AnyToAddrOp                       -> unhandledPrimop op
    
    1166 1166
       MkApUpd0_Op                       -> unhandledPrimop op
    
    1167
    -  NewUDCOp                          -> unhandledPrimop op
    
    1167
    +  NewNullaryClosureOp                          -> unhandledPrimop op
    
    1168 1168
       NewBCOOp                          -> unhandledPrimop op
    
    1169 1169
       UnpackClosureOp                   -> unhandledPrimop op
    
    1170 1170
       ClosureSizeOp                     -> unhandledPrimop op
    

  • libraries/ghci/GHCi/CreateBCO.hs
    ... ... @@ -14,7 +14,7 @@
    14 14
     --
    
    15 15
     
    
    16 16
     -- | Create real byte-code objects from 'ResolvedBCO's and 'NullaryDataConApp's.
    
    17
    -module GHCi.CreateBCO (createBCOs, createUDCs) where
    
    17
    +module GHCi.CreateBCO (createBCOs, createNullaryClosures) where
    
    18 18
     
    
    19 19
     import Prelude -- See note [Why do we import Prelude here?]
    
    20 20
     import GHCi.BreakArray
    
    ... ... @@ -28,20 +28,20 @@ import Data.Array.Base
    28 28
     import Foreign hiding (newArray)
    
    29 29
     import Unsafe.Coerce (unsafeCoerce)
    
    30 30
     import GHC.Arr          ( Array(..) )
    
    31
    -import GHC.Exts   hiding ( BCO, mkApUpd0#, newBCO#, newUDC# )
    
    32
    -import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO#, newUDC# )
    
    31
    +import GHC.Exts   hiding ( BCO, mkApUpd0#, newBCO#, newNullaryClosure# )
    
    32
    +import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO#, newNullaryClosure# )
    
    33 33
     import GHC.IO
    
    34 34
     import GHC.Exts.Heap ( StgInfoTable )
    
    35 35
     import Control.Exception ( ErrorCall(..) )
    
    36 36
     
    
    37
    -createUDCs :: [RemotePtr StgInfoTable] -> IO [HValueRef]
    
    38
    -createUDCs dcas = do
    
    39
    -  mapM createUnliftedDataConstructor dcas
    
    37
    +createNullaryClosures :: [RemotePtr StgInfoTable] -> IO [HValueRef]
    
    38
    +createNullaryClosures dcas = do
    
    39
    +  mapM createNullaryClosure dcas
    
    40 40
     
    
    41
    -createUnliftedDataConstructor :: RemotePtr StgInfoTable -> IO HValueRef
    
    42
    -createUnliftedDataConstructor infoTablePtr =
    
    41
    +createNullaryClosure :: RemotePtr StgInfoTable -> IO HValueRef
    
    42
    +createNullaryClosure infoTablePtr =
    
    43 43
       let !(Ptr !addr#) = fromRemotePtr infoTablePtr
    
    44
    -  in  IO $ \s -> newUDC# addr# s
    
    44
    +  in  IO $ \s -> newNullaryClosure# addr# s
    
    45 45
     
    
    46 46
     createBCOs :: [ResolvedBCO] -> IO [HValueRef]
    
    47 47
     createBCOs bcos = do
    

  • libraries/ghci/GHCi/Message.hs
    ... ... @@ -106,7 +106,7 @@ data Message a where
    106 106
       -- see Note [Parallelize CreateBCOs serialization]
    
    107 107
       CreateBCOs :: [ResolvedBCO] -> Message [HValueRef]
    
    108 108
     
    
    109
    -  CreateUDCs :: [ResolvedUDC] -> Message [HValueRef]
    
    109
    +  CreateNullaryClosures :: [ResolvedNullaryClosure] -> Message [HValueRef]
    
    110 110
     
    
    111 111
       -- | Release 'HValueRef's
    
    112 112
       FreeHValueRefs :: [HValueRef] -> Message ()
    
    ... ... @@ -588,7 +588,7 @@ getMessage = do
    588 588
           38 -> Msg <$> (ResumeSeq <$> get)
    
    589 589
           39 -> Msg <$> (LookupSymbolInDLL <$> get <*> get)
    
    590 590
           40 -> Msg <$> (WhereFrom <$> get)
    
    591
    -      41 -> Msg <$> (CreateUDCs <$> get)
    
    591
    +      41 -> Msg <$> (CreateNullaryClosures <$> get)
    
    592 592
           _  -> error $ "Unknown Message code " ++ (show b)
    
    593 593
     
    
    594 594
     putMessage :: Message a -> Put
    
    ... ... @@ -635,7 +635,7 @@ putMessage m = case m of
    635 635
       ResumeSeq a                 -> putWord8 38 >> put a
    
    636 636
       LookupSymbolInDLL dll str   -> putWord8 39 >> put dll >> put str
    
    637 637
       WhereFrom a                 -> putWord8 40 >> put a
    
    638
    -  CreateUDCs ptr              -> putWord8 41 >> put ptr
    
    638
    +  CreateNullaryClosures ptr              -> putWord8 41 >> put ptr
    
    639 639
     
    
    640 640
     {-
    
    641 641
     Note [Parallelize CreateBCOs serialization]
    

  • libraries/ghci/GHCi/ResolvedBCO.hs
    ... ... @@ -4,7 +4,7 @@
    4 4
     module GHCi.ResolvedBCO
    
    5 5
       ( ResolvedBCO(..)
    
    6 6
       , ResolvedBCOPtr(..)
    
    7
    -  , ResolvedUDC(..)
    
    7
    +  , ResolvedNullaryClosure(..)
    
    8 8
       , isLittleEndian
    
    9 9
       , BCOByteArray(..)
    
    10 10
       , mkBCOByteArray
    
    ... ... @@ -52,7 +52,7 @@ instance Binary ConInfoTable
    52 52
     instance NFData ConInfoTable
    
    53 53
     
    
    54 54
     -- -----------------------------------------------------------------------------
    
    55
    --- ResolvedUDC
    
    55
    +-- ResolvedNullaryClosure
    
    56 56
     
    
    57 57
     -- | A 'ResolvedBCO' is one in which all the 'Name' references have been
    
    58 58
     -- resolved to actual addresses or 'RemoteHValues'.
    
    ... ... @@ -69,11 +69,11 @@ data ResolvedBCO
    69 69
        }
    
    70 70
        deriving (Generic, Show)
    
    71 71
     
    
    72
    --- | A 'ResolvedUDC' is one in which all arguments have been applied to
    
    72
    +-- | A 'ResolvedNullaryClosure' is one in which all arguments have been applied to
    
    73 73
     -- a (potentially unlifted) data constructor.
    
    74
    -newtype ResolvedUDC
    
    75
    -   = ResolvedUDC {
    
    76
    -        unliftedDataConInfo :: ConInfoTable -- RemotePtr StgInfoTable
    
    74
    +newtype ResolvedNullaryClosure
    
    75
    +   = ResolvedNullaryClosure {
    
    76
    +        unliftedDataConInfo :: ConInfoTable
    
    77 77
        }
    
    78 78
        deriving (Binary, Generic, NFData, Show)
    
    79 79
     
    

  • libraries/ghci/GHCi/Run.hs
    ... ... @@ -79,8 +79,8 @@ run m = case m of
    79 79
       MkConInfoTable infoTable -> convertInfoTable infoTable
    
    80 80
       ResolveObjs -> resolveObjs
    
    81 81
       FindSystemLibrary str -> findSystemLibrary str
    
    82
    -  CreateUDCs dcas ->
    
    83
    -    traverse (convertInfoTable . unliftedDataConInfo) dcas >>= createUDCs
    
    82
    +  CreateNullaryClosures dcas ->
    
    83
    +    traverse (convertInfoTable . unliftedDataConInfo) dcas >>= createNullaryClosures
    
    84 84
       CreateBCOs bcos -> createBCOs bcos
    
    85 85
       LookupClosure str -> lookupClosure str
    
    86 86
     #endif
    

  • libraries/ghci/ghci.cabal.in
    ... ... @@ -83,6 +83,7 @@ library
    83 83
             GHCi.Utils
    
    84 84
     
    
    85 85
         Build-Depends:
    
    86
    +        rts,
    
    86 87
             array            == 0.5.*,
    
    87 88
             base             >= 4.8 && < 4.23,
    
    88 89
             binary           == 0.8.*,
    
    ... ... @@ -94,7 +95,6 @@ library
    94 95
             ghc-heap         >= 9.10.1 && <=@ProjectVersionMunged@,
    
    95 96
             ghc-internal     >= 9.1001.0 && <=@ProjectVersionForLib@.0,
    
    96 97
             ghc-prim         >= 0.5.0 && < 0.14,
    
    97
    -        rts,
    
    98 98
             transformers     >= 0.5 && < 0.7
    
    99 99
     
    
    100 100
         if flag(bootstrap)
    

  • rts/PrimOps.cmm
    ... ... @@ -2145,7 +2145,7 @@ stg_deRefStablePtrzh ( P_ sp )
    2145 2145
        Bytecode object primitives
    
    2146 2146
        -------------------------------------------------------------------------  */
    
    2147 2147
     
    
    2148
    -stg_newUDHzh ( W_ datacon_itbl )
    
    2148
    +stg_newNullaryClosurezh ( W_ datacon_itbl )
    
    2149 2149
     {
    
    2150 2150
         W_ p;
    
    2151 2151
         ALLOC_PRIM(SIZEOF_StgHeader);