[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: compiler: Always load GHC.Data.FastString optimised into GHCi

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Feb 3 23:50:41 UTC 2025



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00
compiler: Always load GHC.Data.FastString optimised into GHCi

The FastString table is shared between the boot compiler and interpreted
compiler. Therefore it's very important the representation of
`FastString` matches in both cases. Otherwise, the interpreter will read
a FastString from the shared variable but place the fields in the wrong
place which leads to segfaults.

Ideally this state would not be shared, but for now we can always
compile both with `-O2` and this leads to a working interpreter.

- - - - -
05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00
RTS: Fix compile on powerpc64 ELF v1

Cabal does not know about the different ABIs for powerpc64 and compiles
StgCRunAsm.S unconditionally. The old make-based build system excluded
this file from the build and it was OK to signal an error when it was
compiled accidentally.

With this patch we compile StgCRunAsm.S to an empty file, which fixes
the build.

Fixes #25700

- - - - -
24f6f98a by Matthew Pickering at 2025-02-03T18:50:25-05:00
interpreter: Always print unit and module name in BCO_NAME instruction

Currently the BCO_Name instruction is a bit difficult to use since the
names are not qualified by the module they come from. When you have a
very generic name such as "wildX4", it becomes impossible to work out
which module the identifier comes from.

Fixes #25694

- - - - -
efec7a70 by Ben Gamari at 2025-02-03T18:50:25-05:00
upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th


(cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7)

Co-authored-by: Ben Gamari <bgamari.foss at gmail.com>
- - - - -


4 changed files:

- .gitlab/rel_eng/upload_ghc_libs.py
- compiler/GHC/Data/FastString.hs
- compiler/GHC/StgToByteCode.hs
- rts/StgCRunAsm.S


Changes:

=====================================
.gitlab/rel_eng/upload_ghc_libs.py
=====================================
@@ -94,9 +94,23 @@ def prep_ghc():
     build_copy_file(PACKAGES['ghc'], 'GHC/Settings/Config.hs')
 
 def prep_ghc_boot_th():
-    # Drop ghc-internal from `hs-source-dirs` as Hackage rejects this
+    # Drop references to `ghc-internal` from `hs-source-dirs` as Hackage rejects
+    # out-of-sdist references and this packages is only uploaded for documentation
+    # purposes.
     modify_file(PACKAGES['ghc-boot-th'], 'ghc-boot-th.cabal',
-                lambda s: s.replace('../ghc-internal/src', ''))
+                lambda s: s.replace('../ghc-internal/src', '')
+                           .replace('GHC.Internal.TH.Lib.Map', '')
+                           .replace('GHC.Internal.TH.PprLib', '')
+                           .replace('GHC.Internal.TH.Ppr', '')
+                           .replace('GHC.Internal.TH.Lib,', '')
+                           .replace('GHC.Internal.TH.Lib', '')
+                           .replace('GHC.Internal.TH.Lift,', '')
+                           .replace('GHC.Internal.TH.Quote,', '')
+                           .replace('GHC.Internal.TH.Syntax', '')
+                           .replace('GHC.Internal.ForeignSrcLang', '')
+                           .replace('GHC.Internal.LanguageExtensions', '')
+                           .replace('GHC.Internal.Lexeme', '')
+                )
 
 PACKAGES = {
     pkg.name: pkg


=====================================
compiler/GHC/Data/FastString.hs
=====================================
@@ -2,10 +2,19 @@
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE UnboxedTuples #-}
 {-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE CPP #-}
 
 {-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
+#if MIN_VERSION_GLASGOW_HASKELL(9,8,0,0)
+{-# OPTIONS_GHC -fno-unoptimized-core-for-interpreter #-}
+#endif
 -- We always optimise this, otherwise performance of a non-optimised
 -- compiler is severely affected
+--
+-- Also important, if you load this module into GHCi then the data representation of
+-- FastString has to match that of the host compiler due to the shared FastString
+-- table. Otherwise you will get segfaults when the table is consulted and the fields
+-- from the FastString are in an incorrect order.
 
 -- |
 -- There are two principal string types used internally by GHC:


=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -240,11 +240,12 @@ ppBCEnv p
 -- Create a BCO and do a spot of peephole optimisation on the insns
 -- at the same time.
 mkProtoBCO
-   :: (Outputable name)
-   => Platform
-   -> Bool      -- ^ True <=> label with @BCO_NAME@ instruction
-                -- see Note [BCO_NAME]
-   -> name
+   ::
+    Platform
+   -> Maybe Module
+        -- ^ Just cur_mod <=> label with @BCO_NAME@ instruction
+        -- see Note [BCO_NAME]
+   -> Name
    -> BCInstrList
    -> Either  [CgStgAlt] (CgStgRhs)
                 -- ^ original expression; for debugging only
@@ -253,7 +254,7 @@ mkProtoBCO
    -> [StgWord] -- ^ bitmap
    -> Bool      -- ^ True <=> is a return point, rather than a function
    -> [FFIInfo]
-   -> ProtoBCO name
+   -> ProtoBCO Name
 mkProtoBCO platform _add_bco_name nm instrs_ordlist origin arity bitmap_size bitmap is_ret ffis
    = ProtoBCO {
         protoBCOName = nm,
@@ -267,9 +268,9 @@ mkProtoBCO platform _add_bco_name nm instrs_ordlist origin arity bitmap_size bit
      where
 #if MIN_VERSION_rts(1,0,3)
         maybe_add_bco_name instrs
-          | _add_bco_name = BCO_NAME str : instrs
-          where
-            str = BS.pack $ showSDocOneLine defaultSDocContext (ppr nm)
+          | Just cur_mod <- _add_bco_name =
+              let str = BS.pack $ showSDocOneLine defaultSDocContext (pprFullName cur_mod nm)
+              in BCO_NAME str : instrs
 #endif
         maybe_add_bco_name instrs = instrs
 
@@ -1398,7 +1399,7 @@ Note [unboxed tuple bytecodes and tuple_BCO]
 
 tupleBCO :: Platform -> NativeCallInfo -> [(PrimRep, ByteOff)] -> [FFIInfo] -> ProtoBCO Name
 tupleBCO platform args_info args =
-  mkProtoBCO platform False invented_name body_code (Left [])
+  mkProtoBCO platform Nothing invented_name body_code (Left [])
              0{-no arity-} bitmap_size bitmap False{-is alts-}
   where
     {-
@@ -1419,7 +1420,7 @@ tupleBCO platform args_info args =
 
 primCallBCO :: Platform -> NativeCallInfo -> [(PrimRep, ByteOff)] -> [FFIInfo] -> ProtoBCO Name
 primCallBCO platform args_info args =
-  mkProtoBCO platform False invented_name body_code (Left [])
+  mkProtoBCO platform Nothing invented_name body_code (Left [])
              0{-no arity-} bitmap_size bitmap False{-is alts-}
   where
     {-
@@ -2359,8 +2360,12 @@ getHscEnv = BcM $ \st -> return (st, bcm_hsc_env st)
 getProfile :: BcM Profile
 getProfile = targetProfile <$> getDynFlags
 
-shouldAddBcoName :: BcM Bool
-shouldAddBcoName = gopt Opt_AddBcoName <$> getDynFlags
+shouldAddBcoName :: BcM (Maybe Module)
+shouldAddBcoName = do
+  add <- gopt Opt_AddBcoName <$> getDynFlags
+  if add
+    then Just <$> getCurrentModule
+    else return Nothing
 
 emitBc :: ([FFIInfo] -> ProtoBCO Name) -> BcM (ProtoBCO Name)
 emitBc bco


=====================================
rts/StgCRunAsm.S
=====================================
@@ -69,7 +69,7 @@ StgReturn:
 
 	.section	.note.GNU-stack,"", at progbits
 # else // Not ELF v2
-# error Only ELF v2 supported.
+       // ELF v1 is in StgCrun.c
 # endif
 
 #elif defined(powerpc_HOST_ARCH)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54bc5519d7ffcdf3e10b3ac442ee6eda1b7be6c0...efec7a7055433151e4672bf3cf3d56a492f811dd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54bc5519d7ffcdf3e10b3ac442ee6eda1b7be6c0...efec7a7055433151e4672bf3cf3d56a492f811dd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250203/13db1ebd/attachment-0001.html>


More information about the ghc-commits mailing list