[Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] 5 commits: Revert formatting-only change in elf_got.c
Sven Tennie (@supersven)
gitlab at gitlab.haskell.org
Sun Jun 16 17:32:06 UTC 2024
Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC
Commits:
decac423 by Sven Tennie at 2024-06-16T12:57:52+00:00
Revert formatting-only change in elf_got.c
- - - - -
ee06f4bf by Sven Tennie at 2024-06-16T12:58:13+00:00
Add CODEOWNERS entry
- - - - -
05e0f4dd by Sven Tennie at 2024-06-16T13:47:24+00:00
Cleanup RegInfo
- - - - -
2d336c47 by Sven Tennie at 2024-06-16T13:51:45+00:00
Delete ToDo
- - - - -
0cdebb64 by Sven Tennie at 2024-06-16T13:58:05+00:00
fixup! Cleanup RegInfo
- - - - -
4 changed files:
- CODEOWNERS
- compiler/GHC/CmmToAsm/RV64/RegInfo.hs
- compiler/GHC/Driver/DynFlags.hs
- rts/linker/elf_got.c
Changes:
=====================================
CODEOWNERS
=====================================
@@ -40,6 +40,7 @@
/compiler/GHC/HsToCore/Foreign/Wasm.hs @TerrorJack
/compiler/GHC/Tc/Deriv/ @RyanGlScott
/compiler/GHC/CmmToAsm/ @simonmar @bgamari @AndreasK
+/compiler/GHC/CmmToAsm/RV64/ @supersven @angerman
/compiler/GHC/CmmToAsm/Wasm/ @TerrorJack
/compiler/GHC/CmmToLlvm/ @angerman
/compiler/GHC/StgToCmm/ @simonmar @osa1
=====================================
compiler/GHC/CmmToAsm/RV64/RegInfo.hs
=====================================
@@ -1,31 +1,41 @@
-module GHC.CmmToAsm.RV64.RegInfo where
+-- | Minimum viable implementation of jump short-cutting: No short-cutting.
+--
+-- The functions here simply implement the no-short-cutting case. Implementing
+-- the real behaviour would be a great optimization in future.
+module GHC.CmmToAsm.RV64.RegInfo
+ ( getJumpDestBlockId,
+ canShortcut,
+ shortcutStatics,
+ shortcutJump,
+ JumpDest (..),
+ )
+where
-import GHC.Prelude
-
-import GHC.CmmToAsm.RV64.Instr
-import GHC.Cmm.BlockId
import GHC.Cmm
-
+import GHC.Cmm.BlockId
+import GHC.CmmToAsm.RV64.Instr
+import GHC.Prelude
import GHC.Utils.Outputable
-data JumpDest = DestBlockId BlockId
+newtype JumpDest = DestBlockId BlockId
--- Debug Instance
instance Outputable JumpDest where
ppr (DestBlockId bid) = text "jd<blk>:" <> ppr bid
--- TODO: documen what this does. See Ticket 19914
+-- | Extract BlockId
+--
+-- Never `Nothing` for Riscv64 NCG.
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId (DestBlockId bid) = Just bid
--- TODO: document what this does. See Ticket 19914
+-- No `Instr`s can bet shortcut (for now)
canShortcut :: Instr -> Maybe JumpDest
canShortcut _ = Nothing
--- TODO: document what this does. See Ticket 19914
+-- Identity of the provided `RawCmmStatics`
shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics _ other_static = other_static
--- TODO: document what this does. See Ticket 19914
+-- Identity of the provided `Instr`
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
-shortcutJump _ other = other
\ No newline at end of file
+shortcutJump _ other = other
=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -1325,7 +1325,6 @@ default_PIC platform =
(OSDarwin, ArchAArch64) -> [Opt_PIC]
(OSLinux, ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs]
(OSLinux, ArchARM {}) -> [Opt_PIC, Opt_ExternalDynamicRefs]
- -- TODO: Check if we need ExternalDynamicRefs on RISCV64
(OSLinux, ArchRISCV64 {}) -> [Opt_PIC, Opt_ExternalDynamicRefs]
(OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in
-- OpenBSD since 5.3 release
=====================================
rts/linker/elf_got.c
=====================================
@@ -9,20 +9,22 @@
* Check if we need a global offset table slot for a
* given symbol
*/
-bool needGotSlot(Elf_Sym *symbol) {
- /* using global here should give an upper bound */
- /* I don't believe we need to relocate STB_LOCAL
- * symbols via the GOT; however I'm unsure about
- * STB_WEAK.
- *
- * Any more restrictive filter here would result
- * in a smaller GOT, which is preferable.
- */
- return ELF_ST_BIND(symbol->st_info) == STB_GLOBAL ||
- ELF_ST_BIND(symbol->st_info) == STB_WEAK
- // Section symbols exist primarily for relocation
- // and as such may need a GOT slot.
- || ELF_ST_TYPE(symbol->st_info) == STT_SECTION;
+bool
+needGotSlot(Elf_Sym * symbol) {
+ /* using global here should give an upper bound */
+ /* I don't believe we need to relocate STB_LOCAL
+ * symbols via the GOT; however I'm unsure about
+ * STB_WEAK.
+ *
+ * Any more restrictive filter here would result
+ * in a smaller GOT, which is preferable.
+ */
+ return ELF_ST_BIND(symbol->st_info) == STB_GLOBAL
+ || ELF_ST_BIND(symbol->st_info) == STB_WEAK
+ // Section symbols exist primarily for relocation
+ // and as such may need a GOT slot.
+ || ELF_ST_TYPE(symbol->st_info) == STT_SECTION;
+
}
bool
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b64352ba474f1fe1bab41b6620afdcdd2994d97...0cdebb64c50626c203a42fa16af11e6ebc8be64b
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b64352ba474f1fe1bab41b6620afdcdd2994d97...0cdebb64c50626c203a42fa16af11e6ebc8be64b
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/20240616/335874cb/attachment-0001.html>
More information about the ghc-commits
mailing list