[Git][ghc/ghc][wip/sym-type] rts/linker: Clearly define SymType

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Mon Oct 23 23:29:01 UTC 2023



Ben Gamari pushed to branch wip/sym-type at Glasgow Haskell Compiler / GHC


Commits:
b1341272 by Ben Gamari at 2023-10-23T19:28:53-04:00
rts/linker: Clearly define SymType

Previously SymType was both an enumeration of three symbol types *and*
an orthogonal flag (`DUP_DISCARD`, introduced in !9475). This was quite
fragile as it meant that to extract the symbol type one had to careful
mask out the flag. Naturally this wasn't done consistently.

Fix this by renaming the field to `flags` and adding an accessor.

Fixes #24117.

- - - - -


5 changed files:

- rts/Linker.c
- rts/LinkerInternals.h
- rts/linker/Elf.c
- rts/linker/MachO.c
- rts/linker/PEi386.c


Changes:

=====================================
rts/Linker.c
=====================================
@@ -226,7 +226,7 @@ static void ghciRemoveSymbolTable(StrHashTable *table, const SymbolName* key,
 static const char *
 symbolTypeString (SymType type)
 {
-    switch (type & ~SYM_TYPE_DUP_DISCARD) {
+    switch (type) {
         case SYM_TYPE_CODE: return "code";
         case SYM_TYPE_DATA: return "data";
         case SYM_TYPE_INDIRECT_DATA: return "indirect-data";
@@ -262,6 +262,7 @@ int ghciInsertSymbolTable(
    SymbolAddr* data,
    SymStrength strength,
    SymType type,
+   uint16_t flags,
    ObjectCode *owner)
 {
    RtsSymbolInfo *pinfo = lookupStrHashTable(table, key);
@@ -271,21 +272,21 @@ int ghciInsertSymbolTable(
       pinfo->value = data;
       pinfo->owner = owner;
       pinfo->strength = strength;
-      pinfo->type = type;
+      pinfo->flags = (uint16_t) type | flags;
       insertStrHashTable(table, key, pinfo);
       return 1;
    }
-   else if (pinfo->type ^ type)
+   else if (getRtsSymbolType(pinfo) != type)
    {
        /* We were asked to discard the symbol on duplicates, do so quietly.  */
-       if (!(type & SYM_TYPE_DUP_DISCARD))
+       if (!(flags & SYM_FLAG_DUP_DISCARD))
        {
          debugBelch("Symbol type mismatch.\n");
          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",
                     pinfo->owner ? pinfo->owner->fileName : WSTR("<builtin>"),
-                    symbolTypeString(pinfo->type));
+                    symbolTypeString(getRtsSymbolType(pinfo)));
        }
        return 1;
    }
@@ -466,7 +467,7 @@ initLinker_ (int retain_cafs)
     for (const RtsSymbolVal *sym = rtsSyms; sym->lbl != NULL; sym++) {
         if (! ghciInsertSymbolTable(WSTR("(GHCi built-in symbols)"),
                                     symhash, sym->lbl, sym->addr,
-                                    sym->strength, sym->type, NULL)) {
+                                    sym->strength, sym->type, 0, NULL)) {
             barf("ghciInsertSymbolTable failed");
         }
         IF_DEBUG(linker, debugBelch("initLinker: inserting rts symbol %s, %p\n", sym->lbl, sym->addr));
@@ -476,7 +477,7 @@ initLinker_ (int retain_cafs)
     if (! ghciInsertSymbolTable(WSTR("(GHCi built-in symbols)"), symhash,
                                 MAYBE_LEADING_UNDERSCORE_STR("newCAF"),
                                 retain_cafs ? newRetainedCAF : newGCdCAF,
-                                HS_BOOL_FALSE, SYM_TYPE_CODE, NULL)) {
+                                HS_BOOL_FALSE, SYM_TYPE_CODE, 0, NULL)) {
         barf("ghciInsertSymbolTable failed");
     }
 
@@ -864,7 +865,7 @@ HsBool removeLibrarySearchPath(HsPtr dll_path_index)
 HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data)
 {
     return ghciInsertSymbolTable(obj_name, symhash, key, data, HS_BOOL_FALSE,
-                                 SYM_TYPE_CODE, NULL);
+                                 SYM_TYPE_CODE, 0, NULL);
 }
 
 /* -----------------------------------------------------------------------------
@@ -961,7 +962,7 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent, SymTy
         if (strcmp(lbl, "__fini_array_start") == 0) { return (SymbolAddr *) &RTS_NO_FINI; }
         if (type) {
             // This is an assumption
-            *type = pinfo->type;
+            *type = getRtsSymbolType(pinfo);
         }
 
         if (dependent) {
@@ -1696,7 +1697,7 @@ int ocTryLoad (ObjectCode* oc) {
             && !ghciInsertSymbolTable(oc->fileName, symhash, symbol.name,
                                       symbol.addr,
                                       isSymbolWeak(oc, symbol.name),
-                                      symbol.type, oc)) {
+                                      symbol.type, 0, oc)) {
             return 0;
         }
     }


=====================================
rts/LinkerInternals.h
=====================================
@@ -55,17 +55,27 @@ typedef struct _Section    Section;
 
 /* What kind of thing a symbol identifies. We need to know this to determine how
  * to process overflowing relocations. See Note [Processing overflowed relocations].
- * This is bitfield however only the option SYM_TYPE_DUP_DISCARD can be combined
- * with the other values. */
+ */
 typedef enum _SymType {
     SYM_TYPE_CODE = 1 << 0, /* the symbol is a function and can be relocated via a jump island */
     SYM_TYPE_DATA = 1 << 1, /* the symbol is data */
     SYM_TYPE_INDIRECT_DATA = 1 << 2, /* see Note [_iob_func symbol] */
-    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.  */
 } SymType;
 
+#define SYM_TYPE_MASK (SYM_TYPE_CODE | SYM_TYPE_DATA | SYM_TYPE_INDIRECT_DATA)
+
+INLINE_HEADER SymType symbolFlagsToSymbolType(uint16_t flags) {
+    return (SymType) (flags & SYM_TYPE_MASK);
+}
+
+/*
+ * The symbol is a symbol in a BFD import library
+ * however if a duplicate is found with a mismatching
+ * SymType then discard this one.
+ *
+ */
+#define SYM_FLAG_DUP_DISCARD (1 << 3)
+
 
 #if defined(OBJFORMAT_ELF)
 #  include "linker/ElfTypes.h"
@@ -438,9 +448,14 @@ typedef struct _RtsSymbolInfo {
     SymbolAddr* value;
     ObjectCode *owner;
     SymStrength strength;
-    SymType type;
+    // This is a bitfield combining SymType with the SYM_FLAG_* flags.
+    uint16_t flags;
 } RtsSymbolInfo;
 
+INLINE_HEADER SymType getRtsSymbolType(RtsSymbolInfo *pinfo) {
+    return symbolFlagsToSymbolType(pinfo->flags);
+}
+
 #include "BeginPrivate.h"
 
 void exitLinker( void );
@@ -466,6 +481,8 @@ int ghciInsertSymbolTable(
     SymbolAddr* data,
     SymStrength weak,
     SymType type,
+    // One of SYM_FLAG_*
+    uint16_t flags,
     ObjectCode *owner);
 
 /* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a


=====================================
rts/linker/Elf.c
=====================================
@@ -1083,7 +1083,7 @@ ocGetNames_ELF ( ObjectCode* oc )
                            setWeakSymbol(oc, nm);
                        }
                        if (!ghciInsertSymbolTable(oc->fileName, symhash,
-                                                  nm, symbol->addr, isWeak, sym_type, oc)
+                                                  nm, symbol->addr, isWeak, sym_type, 0, oc)
                            ) {
                            goto fail;
                        }


=====================================
rts/linker/MachO.c
=====================================
@@ -1390,14 +1390,15 @@ ocGetNames_MachO(ObjectCode* oc)
                     {
                             IF_DEBUG(linker_verbose, debugBelch("ocGetNames_MachO: inserting %s\n", nm));
                             SymbolAddr* addr = oc->info->macho_symbols[i].addr;
-                            // TODO: Make figure out how to determine this from the object file
-                            SymType sym_type = SYM_TYPE_CODE;
+                            // TODO: Figure out how to determine this from the object file
+                            const SymType sym_type = SYM_TYPE_CODE;
                             ghciInsertSymbolTable( oc->fileName
                                                  , symhash
                                                  , nm
                                                  , addr
                                                  , HS_BOOL_FALSE
                                                  , sym_type
+                                                 , 0
                                                  , oc);
 
                             oc->symbols[curSymbol].name = nm;
@@ -1440,7 +1441,7 @@ ocGetNames_MachO(ObjectCode* oc)
 
                 IF_DEBUG(linker_verbose, debugBelch("ocGetNames_MachO: inserting common symbol: %s\n", nm));
                 ghciInsertSymbolTable(oc->fileName, symhash, nm,
-                                       (void*)commonCounter, HS_BOOL_FALSE, sym_type, oc);
+                                       (void*)commonCounter, HS_BOOL_FALSE, sym_type, 0, oc);
                 oc->symbols[curSymbol].name = nm;
                 oc->symbols[curSymbol].addr = oc->info->macho_symbols[i].addr;
                 curSymbol++;


=====================================
rts/linker/PEi386.c
=====================================
@@ -299,7 +299,7 @@
    These two issues mean that for GHC we need to take a different approach
    to handling import libraries.  For normal C libraries we have proper
    differentiation between CODE and DATA.   For GHC produced import libraries
-   we do not.   As such the SYM_TYPE_DUP_DISCARD tells the linker that if a
+   we do not.   As such the SYM_FLAG_DUP_DISCARD tells the linker that if a
    duplicate symbol is found, and we were going to discard it anyway, just do
    so quitely.  This works because the RTS symbols themselves are provided by
    the currently loaded RTS as built-in symbols.
@@ -438,7 +438,7 @@ void initLinker_PEi386(void)
     if (!ghciInsertSymbolTable(WSTR("(GHCi/Ld special symbols)"),
                                symhash, "__image_base__",
                                GetModuleHandleW (NULL), HS_BOOL_TRUE,
-                               SYM_TYPE_CODE, NULL)) {
+                               SYM_TYPE_CODE, 0, NULL)) {
         barf("ghciInsertSymbolTable failed");
     }
 
@@ -1814,9 +1814,8 @@ ocGetNames_PEi386 ( ObjectCode* oc )
           sname = strdup (sname);
           addr  = strdup (addr);
           type = has_code_section ? SYM_TYPE_CODE : SYM_TYPE_DATA;
-          type |= SYM_TYPE_DUP_DISCARD;
           if (!ghciInsertSymbolTable(oc->fileName, symhash, sname,
-                                     addr, false, type, oc)) {
+                                     addr, false, type, SYM_FLAG_DUP_DISCARD, oc)) {
              releaseOcInfo (oc);
              stgFree (oc->image);
              oc->image = NULL;
@@ -1895,7 +1894,7 @@ ocGetNames_PEi386 ( ObjectCode* oc )
           stgFree(tmp);
           sname = strdup (sname);
           if (!ghciInsertSymbolTable(oc->fileName, symhash, sname,
-                                     addr, false, type, oc))
+                                     addr, false, type, 0, oc))
                return false;
 
           break;
@@ -1918,7 +1917,7 @@ ocGetNames_PEi386 ( ObjectCode* oc )
          }
 
          if (! ghciInsertSymbolTable(oc->fileName, symhash, sname, addr,
-                                     isWeak, type, oc))
+                                     isWeak, type, 0, oc))
              return false;
       } else {
           /* We're skipping the symbol, but if we ever load this
@@ -2321,7 +2320,9 @@ SymbolAddr *lookupSymbol_PEi386(SymbolName *lbl, ObjectCode *dependent, SymType
         sym = lookupSymbolInDLLs(lbl, dependent);
         return sym; // might be NULL if not found
     } else {
-        if (type) *type = pinfo->type;
+        if (type) {
+            *type = getRtsSymbolType(pinfo);
+        }
 
         if (pinfo && pinfo->owner && isSymbolImport (pinfo->owner, lbl))
         {



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b13412720f73ba2838dfba8019aba5baa1b638d1
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/20231023/fe202624/attachment-0001.html>


More information about the ghc-commits mailing list