[Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-0006-Adds-support-for-Hidden-symbols] RTS linker: add support for hidden symbols (#25191)
Sylvain Henry (@hsyl20)
gitlab at gitlab.haskell.org
Tue Sep 3 14:20:32 UTC 2024
Sylvain Henry pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-0006-Adds-support-for-Hidden-symbols at Glasgow Haskell Compiler / GHC
Commits:
f3b98dbc by doyougnu at 2024-09-03T16:19:57+02:00
RTS linker: add support for hidden symbols (#25191)
Add linker support for hidden symbols. We basically treat them as weak
symbols.
Patch upstreamed from haskell.nix
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>
- - - - -
11 changed files:
- rts/Linker.c
- rts/LinkerInternals.h
- rts/linker/Elf.c
- rts/linker/ElfTypes.h
- rts/linker/PEi386.c
- testsuite/tests/rts/linker/Makefile
- + testsuite/tests/rts/linker/T25191.hs
- + testsuite/tests/rts/linker/T25191.stdout
- + testsuite/tests/rts/linker/T25191_foo1.c
- + testsuite/tests/rts/linker/T25191_foo2.c
- testsuite/tests/rts/linker/all.T
Changes:
=====================================
rts/Linker.c
=====================================
@@ -232,11 +232,11 @@ static void ghciRemoveSymbolTable(StrHashTable *table, const SymbolName* key,
static const char *
symbolTypeString (SymType type)
{
- switch (type & ~SYM_TYPE_DUP_DISCARD) {
+ switch (type & ~(SYM_TYPE_DUP_DISCARD | SYM_TYPE_HIDDEN)) {
case SYM_TYPE_CODE: return "code";
case SYM_TYPE_DATA: return "data";
case SYM_TYPE_INDIRECT_DATA: return "indirect-data";
- default: barf("symbolTypeString: unknown symbol type");
+ default: barf("symbolTypeString: unknown symbol type (%d)", type);
}
}
@@ -283,10 +283,19 @@ int ghciInsertSymbolTable(
}
else if (pinfo->type ^ type)
{
+ if(pinfo->type & SYM_TYPE_HIDDEN)
+ {
+ /* The existing symbol is hidden, let's replace it */
+ pinfo->value = data;
+ pinfo->owner = owner;
+ pinfo->strength = strength;
+ pinfo->type = type;
+ return 1;
+ }
/* We were asked to discard the symbol on duplicates, do so quietly. */
- if (!(type & SYM_TYPE_DUP_DISCARD))
+ if (!(type & (SYM_TYPE_DUP_DISCARD | SYM_TYPE_HIDDEN)))
{
- debugBelch("Symbol type mismatch.\n");
+ debugBelch("Symbol type mismatch (existing %d, new %d).\n", pinfo->type, type);
debugBelch("Symbol %s was defined by %" PATH_FMT " to be a %s symbol.\n",
key, obj_name, symbolTypeString(type));
debugBelch(" yet was defined by %" PATH_FMT " to be a %s symbol.\n",
=====================================
rts/LinkerInternals.h
=====================================
@@ -64,6 +64,8 @@ typedef enum _SymType {
SYM_TYPE_DUP_DISCARD = 1 << 3, /* the symbol is a symbol in a BFD import library
however if a duplicate is found with a mismatching
SymType then discard this one. */
+ SYM_TYPE_HIDDEN = 1 << 4, /* the symbol is hidden and should not be exported */
+
} SymType;
=====================================
rts/linker/Elf.c
=====================================
@@ -1073,6 +1073,9 @@ ocGetNames_ELF ( ObjectCode* oc )
} else {
sym_type = SYM_TYPE_DATA;
}
+ if(ELF_ST_VISIBILITY(symbol->elf_sym->st_other) == STV_HIDDEN) {
+ sym_type |= SYM_TYPE_HIDDEN;
+ }
/* And the decision is ... */
=====================================
rts/linker/ElfTypes.h
=====================================
@@ -33,6 +33,9 @@
#define Elf_Sym Elf64_Sym
#define Elf_Rel Elf64_Rel
#define Elf_Rela Elf64_Rela
+#if !defined(ELF_ST_VISIBILITY)
+#define ELF_ST_VISIBILITY ELF64_ST_VISIBILITY
+#endif
#if !defined(ELF_ST_TYPE)
#define ELF_ST_TYPE ELF64_ST_TYPE
#endif
@@ -57,6 +60,9 @@
#define Elf_Sym Elf32_Sym
#define Elf_Rel Elf32_Rel
#define Elf_Rela Elf32_Rela
+#if !defined(ELF_ST_VISIBILITY)
+#define ELF_ST_VISIBILITY ELF32_ST_VISIBILITY
+#endif /* ELF_ST_VISIBILITY */
#if !defined(ELF_ST_TYPE)
#define ELF_ST_TYPE ELF32_ST_TYPE
#endif /* ELF_ST_TYPE */
=====================================
rts/linker/PEi386.c
=====================================
@@ -1891,6 +1891,9 @@ ocGetNames_PEi386 ( ObjectCode* oc )
sname[size-start]='\0';
stgFree(tmp);
sname = strdup (sname);
+ if(secNumber == IMAGE_SYM_UNDEFINED)
+ type |= SYM_TYPE_HIDDEN;
+
if (!ghciInsertSymbolTable(oc->fileName, symhash, sname,
addr, false, type, oc))
return false;
@@ -1905,6 +1908,8 @@ ocGetNames_PEi386 ( ObjectCode* oc )
&& (!section || (section && section->kind != SECTIONKIND_IMPORT))) {
/* debugBelch("addSymbol %p `%s' Weak:%lld \n", addr, sname, isWeak); */
sname = strdup (sname);
+ if(secNumber == IMAGE_SYM_UNDEFINED)
+ type |= SYM_TYPE_HIDDEN;
IF_DEBUG(linker_verbose, debugBelch("addSymbol %p `%s'\n", addr, sname));
ASSERT(i < (uint32_t)oc->n_symbols);
oc->symbols[i].name = sname;
@@ -1936,7 +1941,7 @@ static size_t
makeSymbolExtra_PEi386( ObjectCode* oc, uint64_t index STG_UNUSED, size_t s, char* symbol STG_UNUSED, SymType type )
{
SymbolExtra *extra;
- switch(type & ~SYM_TYPE_DUP_DISCARD) {
+ switch(type & ~(SYM_TYPE_DUP_DISCARD | SYM_TYPE_HIDDEN)) {
case SYM_TYPE_CODE: {
// jmp *-14(%rip)
extra = m32_alloc(oc->rx_m32, sizeof(SymbolExtra), 8);
=====================================
testsuite/tests/rts/linker/Makefile
=====================================
@@ -145,3 +145,10 @@ reloc-none:
"$(TEST_HC)" load-object.c -o load-object -no-hs-main -debug
"$(TEST_HC)" -c reloc-none.c -o reloc-none.o
./load-object reloc-none.o
+
+.PHONY: T25191
+T25191:
+ "$(TEST_HC)" -c T25191_foo1.c -o foo1.o -v0
+ "$(TEST_HC)" -c T25191_foo2.c -o foo2.o -v0
+ "$(TEST_HC)" T25191.hs -v0
+ ./T25191
=====================================
testsuite/tests/rts/linker/T25191.hs
=====================================
@@ -0,0 +1,29 @@
+{-# LANGUAGE ForeignFunctionInterface, CPP #-}
+import Foreign.C.String
+import Control.Monad
+import System.FilePath
+import Foreign.Ptr
+
+-- Type of paths is different on Windows
+#if defined(mingw32_HOST_OS)
+type PathString = CWString
+withPathString = withCWString
+#else
+type PathString = CString
+withPathString = withCString
+#endif
+
+main = do
+ initLinker
+ r1 <- withPathString "foo1.o" loadObj
+ when (r1 /= 1) $ error "loadObj failed"
+ r2 <- withPathString "foo2.o" loadObj
+ when (r2 /= 1) $ error "loadObj failed"
+ r <- resolveObjs
+ when (r /= 1) $ error "resolveObj failed"
+ putStrLn "success"
+
+foreign import ccall "initLinker" initLinker :: IO ()
+foreign import ccall "addDLL" addDLL :: PathString -> IO CString
+foreign import ccall "loadObj" loadObj :: PathString -> IO Int
+foreign import ccall "resolveObjs" resolveObjs :: IO Int
=====================================
testsuite/tests/rts/linker/T25191.stdout
=====================================
@@ -0,0 +1 @@
+success
=====================================
testsuite/tests/rts/linker/T25191_foo1.c
=====================================
@@ -0,0 +1,10 @@
+#include <stdio.h>
+
+void __attribute__ ((__visibility__ ("hidden"))) foo(void) {
+ printf("HIDDEN FOO\n");
+}
+
+void bar(void) {
+ printf("BAR\n");
+ foo();
+}
=====================================
testsuite/tests/rts/linker/T25191_foo2.c
=====================================
@@ -0,0 +1,8 @@
+#include <stdio.h>
+
+extern void bar(void);
+
+void foo(void) {
+ printf("VISIBLE FOO\n");
+ bar();
+}
=====================================
testsuite/tests/rts/linker/all.T
=====================================
@@ -168,3 +168,11 @@ test('reloc-none',
unless(opsys('linux'), skip),
req_rts_linker],
makefile_test, ['reloc-none'])
+
+test('T25191',
+ [req_rts_linker,
+ extra_files(['T25191_foo1.c','T25191_foo2.c']),
+ when(opsys('darwin'), expect_broken(25191)), # not supported in the MachO linker yet
+ when(opsys('mingw32'), expect_broken(25191)) # not supported in the PE linker yet
+ ],
+ makefile_test, ['T25191'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3b98dbcff144af0163d9ebfe5504f6fba8dfd9d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3b98dbcff144af0163d9ebfe5504f6fba8dfd9d
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/20240903/e6f00c8e/attachment-0001.html>
More information about the ghc-commits
mailing list