[Git][ghc/ghc][wip/supersven/riscv64-ncg] Linker: Belch only when asked

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Wed Feb 21 20:10:29 UTC 2024



Sven Tennie pushed to branch wip/supersven/riscv64-ncg at Glasgow Haskell Compiler / GHC


Commits:
6bacb271 by Sven Tennie at 2024-02-21T21:10:04+01:00
Linker: Belch only when asked

- - - - -


2 changed files:

- rts/linker/elf_plt_riscv64.c
- rts/linker/elf_reloc_riscv64.c


Changes:

=====================================
rts/linker/elf_plt_riscv64.c
=====================================
@@ -44,15 +44,18 @@ bool needStubForRelaRISCV64(Elf_Rela *rela) {
 // riscv64 assembly. (See
 // https://github.com/riscv-non-isa/riscv-elf-psabi-doc/blob/5ffe5b5aeedb37b1c1c0c3d94641267d9ad4795a/riscv-elf.adoc#procedure-linkage-table)
 bool makeStubRISCV64(Stub *s) {
-  uint32_t * P = (uint32_t *)s->addr;
-  int32_t addr = (uint64_t) s->got_addr - (uint64_t) P;
+  uint32_t *P = (uint32_t *)s->addr;
+  int32_t addr = (uint64_t)s->got_addr - (uint64_t)P;
 
   uint64_t hi = (addr + 0x800) >> 12;
   uint64_t lo = addr - (hi << 12);
 
-  debugBelch("makeStubRISCV64: P = %p, got_addr = %p, target = %p, addr = 0x%x "
-             ", hi = 0x%lx, lo = 0x%lx\n",
-             P, s->got_addr, s->target, addr, hi, lo);
+  IF_DEBUG(
+      linker,
+      debugBelch(
+          "makeStubRISCV64: P = %p, got_addr = %p, target = %p, addr = 0x%x "
+          ", hi = 0x%lx, lo = 0x%lx\n",
+          P, s->got_addr, s->target, addr, hi, lo));
 
   // AUIPC ip, %pcrel_hi(addr)
   uint32_t auipcInst = 0b0010111; // opcode


=====================================
rts/linker/elf_reloc_riscv64.c
=====================================
@@ -134,9 +134,9 @@ uint32_t extractBits(uint64_t v, uint32_t begin, uint32_t end) {
 }
 
 uint32_t setLO12_I(uint32_t insn, uint32_t imm) {
-  debugBelch(
-      "setLO12_I: insn 0x%x imm 0x%x (insn & 0xfffff) 0x%x (imm << 20) 0x%x \n",
-      insn, imm, (insn & 0xfffff), (imm << 20));
+  IF_DEBUG(linker, debugBelch("setLO12_I: insn 0x%x imm 0x%x (insn & 0xfffff) "
+                              "0x%x (imm << 20) 0x%x \n",
+                              insn, imm, (insn & 0xfffff), (imm << 20)));
   return (insn & 0xfffff) | (imm << 20);
 }
 
@@ -155,12 +155,14 @@ void setUType(inst_t *loc, uint32_t val) {
 void setIType(inst_t *loc, uint32_t val) {
   uint64_t hi = (val + 0x800) >> 12;
   uint64_t lo = val - (hi << 12);
-  debugBelch("setIType: hi 0x%lx lo 0x%lx\n", hi, lo);
-  debugBelch("setIType: loc %p  *loc 0x%x  val 0x%x\n", loc, *loc, val);
+  IF_DEBUG(linker, debugBelch("setIType: hi 0x%lx lo 0x%lx\n", hi, lo));
+  IF_DEBUG(linker, debugBelch("setIType: loc %p  *loc 0x%x  val 0x%x\n", loc,
+                              *loc, val));
   uint32_t insn = setLO12_I(read32le(loc), lo & 0xfff);
-  debugBelch("setIType: insn 0x%x\n", insn);
+  IF_DEBUG(linker, debugBelch("setIType: insn 0x%x\n", insn));
   write32le(loc, insn);
-  debugBelch("setIType: loc %p  *loc' 0x%x  val 0x%x\n", loc, *loc, val);
+  IF_DEBUG(linker, debugBelch("setIType: loc %p  *loc' 0x%x  val 0x%x\n", loc,
+                              *loc, val));
 }
 
 void setSType(inst_t *loc, uint32_t val) {
@@ -226,11 +228,14 @@ void setCJType(cinst_t *loc, uint32_t val) {
 
 bool encodeAddendRISCV64(Section *section, Elf_Rel *rel, int64_t addend) {
   addr_t P = (addr_t)((uint8_t *)section->start + rel->r_offset);
-  debugBelch("Relocation type %s 0x%lx (%lu) symbol 0x%lx addend 0x%lx (%lu / "
-             "%ld) P 0x%lx\n",
-             relocationTypeToString(rel->r_info), ELF64_R_TYPE(rel->r_info),
-             ELF64_R_TYPE(rel->r_info), ELF64_R_SYM(rel->r_info), addend,
-             addend, addend, P);
+  IF_DEBUG(
+      linker,
+      debugBelch(
+          "Relocation type %s 0x%lx (%lu) symbol 0x%lx addend 0x%lx (%lu / "
+          "%ld) P 0x%lx\n",
+          relocationTypeToString(rel->r_info), ELF64_R_TYPE(rel->r_info),
+          ELF64_R_TYPE(rel->r_info), ELF64_R_SYM(rel->r_info), addend, addend,
+          addend, P));
   switch (ELF64_R_TYPE(rel->r_info)) {
   case R_RISCV_32_PCREL:
   case R_RISCV_32:
@@ -362,8 +367,9 @@ int64_t computeAddend(Section *section, Elf_Rel *rel, ElfSymbol *symbol,
 
   int64_t A = addend;
 
-  debugBelch("%s: P 0x%lx S 0x%lx %s GOT_S 0x%lx A 0x%lx\n",
-             relocationTypeToString(rel->r_info), P, S, symbol->name, GOT_S, A);
+  IF_DEBUG(linker, debugBelch("%s: P 0x%lx S 0x%lx %s GOT_S 0x%lx A 0x%lx\n",
+                              relocationTypeToString(rel->r_info), P, S,
+                              symbol->name, GOT_S, A));
   switch (ELF64_R_TYPE(rel->r_info)) {
   case R_RISCV_32:
     return S + A;
@@ -391,12 +397,14 @@ int64_t computeAddend(Section *section, Elf_Rel *rel, ElfSymbol *symbol,
   case R_RISCV_CALL_PLT: {
     if (findStub(section, (void **)&S, 0)) {
       /* did not find it. Crete a new stub. */
-      if (makeStub(section, (void **)&S, (void*) GOT_S, 0)) {
+      if (makeStub(section, (void **)&S, (void *)GOT_S, 0)) {
         abort(/* could not find or make stub */);
       }
     }
-    debugBelch("S = 0x%lx  A = 0x%lx  P = 0x%lx  (S + A) - P = 0x%lx \n", S, A,
-               P, (S + A) - P);
+    IF_DEBUG(
+        linker,
+        debugBelch("S = 0x%lx  A = 0x%lx  P = 0x%lx  (S + A) - P = 0x%lx \n", S,
+                   A, P, (S + A) - P));
     return (S + A) - P;
   }
   case R_RISCV_ADD8:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6bacb27110508ded1e0108e2d2ebd034eecd5cd5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6bacb27110508ded1e0108e2d2ebd034eecd5cd5
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/20240221/325754d9/attachment-0001.html>


More information about the ghc-commits mailing list