[Git][ghc/ghc][wip/T18857] fixup ShortText & SymbolExtras
Moritz Angermann
gitlab at gitlab.haskell.org
Tue Nov 17 04:28:25 UTC 2020
Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC
Commits:
047ee59e by Moritz Angermann at 2020-11-17T04:28:05+00:00
fixup ShortText & SymbolExtras
- - - - -
5 changed files:
- libraries/ghc-boot/GHC/Data/ShortText.hs
- rts/LinkerInternals.h
- rts/linker/Elf.c
- rts/linker/SymbolExtras.c
- rts/linker/elf_reloc_aarch64.c
Changes:
=====================================
libraries/ghc-boot/GHC/Data/ShortText.hs
=====================================
@@ -1,6 +1,22 @@
-{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-}
+{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-}
{-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
-
+-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore.
+-- LLVM based GHC's fail to compile memcmp ffi calls. These end up as memcmp$def in the llvm ir, however we
+-- don't have any prototypes and subsequently the llvm toolchain chokes on them. Since 7fdcce6d, we use
+-- ShortText for the package database. This however introduces this very module; which through inlining ends
+-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in
+-- the memcmp call we choke on.
+--
+-- The solution thusly is to force late binding via the linker instead of inlining when comping with the
+-- bootstrap compiler. This will produce a slower (slightly less optimised) stage1 compiler only.
+--
+-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion.
+--
+-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler,
+-- we can drop this code as well.
+#if GHC_STAGE < 1
+{-# OPTIONS_GHC -fignore-interface-pragmas #-}
+#endif
-- |
-- An Unicode string for internal GHC use. Meant to replace String
-- in places where being a lazy linked is not very useful and a more
=====================================
rts/LinkerInternals.h
=====================================
@@ -141,7 +141,7 @@ typedef struct _Segment {
int n_sections;
} Segment;
-#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH)
+#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH)
#define NEED_SYMBOL_EXTRAS 1
#endif
=====================================
rts/linker/Elf.c
=====================================
@@ -940,7 +940,7 @@ ocGetNames_ELF ( ObjectCode* oc )
symbol->addr = (SymbolAddr*)(
(intptr_t) oc->sections[secno].start +
(intptr_t) symbol->elf_sym->st_value);
-
+ ASSERT(symbol->addr != 0x0);
if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) {
isLocal = true;
isWeak = false;
@@ -1867,6 +1867,7 @@ ocResolve_ELF ( ObjectCode* oc )
#endif
ASSERT(symbol->elf_sym->st_name == 0);
ASSERT(symbol->elf_sym->st_value == 0);
+ ASSERT(0x0 != oc->sections[ secno ].start);
symbol->addr = oc->sections[ secno ].start;
}
}
@@ -1940,6 +1941,7 @@ int ocRunInit_ELF( ObjectCode *oc )
init_start = (init_t*)init_startC;
init_end = (init_t*)(init_startC + shdr[i].sh_size);
for (init = init_start; init < init_end; init++) {
+ ASSERT(0x0 != *init);
(*init)(argc, argv, envv);
}
}
=====================================
rts/linker/SymbolExtras.c
=====================================
@@ -140,7 +140,12 @@ void ocProtectExtras(ObjectCode* oc)
* non-executable.
*/
} else if (USE_CONTIGUOUS_MMAP || RtsFlags.MiscFlags.linkerAlwaysPic) {
- mmapForLinkerMarkExecutable(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras);
+ // XXX I'm not sure how this is supposed to work.
+ // XXX
+ // XXX oc->symbol_extras would need to be assigned on page boundaries, and mmaped
+ // XXX but this is not guaranteed in any form or fashion?
+ // XXX
+ // mmapForLinkerMarkExecutable(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras);
} else {
/*
* The symbol extras were allocated via m32. They will be protected when
=====================================
rts/linker/elf_reloc_aarch64.c
=====================================
@@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) {
relTab->sectionHeader->sh_link,
ELF64_R_SYM((Elf64_Xword)rel->r_info));
- assert(symbol != NULL);
+ assert(0x0 != symbol);
/* decode implicit addend */
int64_t addend = decodeAddendAarch64(targetSection, rel);
@@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) {
ELF64_R_SYM((Elf64_Xword)rel->r_info));
assert(0x0 != symbol);
+ assert(0x0 != symbol->addr);
/* take explicit addend */
int64_t addend = rel->r_addend;
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/047ee59e16d54893fd49ef15f9527ddfa9d7757a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/047ee59e16d54893fd49ef15f9527ddfa9d7757a
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/20201116/d6da37da/attachment-0001.html>
More information about the ghc-commits
mailing list