[commit: ghc] master: Add ocInit_MachO (938392c)

git at git.haskell.org git at git.haskell.org
Mon Mar 27 03:01:03 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/938392c8515ccbe894714f43852fe604a21ce30b/ghc

>---------------------------------------------------------------

commit 938392c8515ccbe894714f43852fe604a21ce30b
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date:   Tue Mar 21 11:01:11 2017 -0400

    Add ocInit_MachO
    
    This adds ocInit_MachO function, used to populate the extended
    ObjectCode structure, and the corresponding stgFree.
    
    It also adds defines for iOS, such that MachO.o is also compiled for iOS
    targets.
    
    Depends on D3239
    
    ---
    
    This is just one of the pieces for the rts linker
    support for ios (aarch64-macho)
    
    ---
    
    The following diagram and legend tries to explain the dependencies a
    bit:
    ```
      .- D3240
      v
    D3255 <- D3252 <- This <- D3239
      ^
      '- D3238
    ```
    
    - In D3238 we started allowing preloading object code with mmap
      in iOS, where we can't have r+w+x.
    - In D3239 we introduced a richer extension of the object code
      data type to make working with mach-o files easier.
    - In D3240 we set the stage to allow loading archives (.a) on iOS
    - In D3251 we added init and deinit functions to populate and
      depopulate the enriched object code data structure for mach-o
      files.
    - In D3252 we refactored most of the MachO.c file to use the
      new types and data structure.
    - in D3255 we finally introduce the aarch64-mach-o linker.
    
    Reviewers: rwbarton, bgamari, austin, erikd, simonmar
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D3251


>---------------------------------------------------------------

938392c8515ccbe894714f43852fe604a21ce30b
 rts/Linker.c             |  9 ++++++
 rts/linker/LoadArchive.c |  3 ++
 rts/linker/MachO.c       | 81 +++++++++++++++++++++++++++++++++++++++++++++---
 rts/linker/MachO.h       |  4 +++
 4 files changed, 93 insertions(+), 4 deletions(-)

diff --git a/rts/Linker.c b/rts/Linker.c
index 87f1eeb..529af9a 100644
--- a/rts/Linker.c
+++ b/rts/Linker.c
@@ -1186,6 +1186,10 @@ void freeObjectCode (ObjectCode *oc)
     }
 #endif
 
+#if defined(OBJECTFORMAT_MACHO)
+    ocDeinit_MachO(oc);
+#endif
+
     stgFree(oc->fileName);
     stgFree(oc->archiveMemberName);
 
@@ -1389,6 +1393,11 @@ preloadObjectFile (pathchar *path)
 
    oc = mkOc(path, image, fileSize, true, NULL, misalignment);
 
+#ifdef OBJFORMAT_MACHO
+   if (ocVerifyImage_MachO( oc ))
+       ocInit_MachO( oc );
+#endif
+
    return oc;
 }
 
diff --git a/rts/linker/LoadArchive.c b/rts/linker/LoadArchive.c
index f9997cf..a33c00d 100644
--- a/rts/linker/LoadArchive.c
+++ b/rts/linker/LoadArchive.c
@@ -538,6 +538,9 @@ static HsInt loadArchive_ (pathchar *path)
 
             oc = mkOc(path, image, memberSize, false, archiveMemberName
                      , misalignment);
+#ifdef OBJFORMAT_MACHO
+            ocInit_MachO( oc );
+#endif
 
             stgFree(archiveMemberName);
 
diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c
index 55b2bf1..13508fa 100644
--- a/rts/linker/MachO.c
+++ b/rts/linker/MachO.c
@@ -1,6 +1,6 @@
 #include "Rts.h"
 
-#ifdef darwin_HOST_OS
+#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
 
 #include "RtsUtils.h"
 #include "GetEnv.h"
@@ -17,7 +17,7 @@
 #include <mach-o/nlist.h>
 #include <mach-o/reloc.h>
 
-#if defined(HAVE_SYS_MMAN_H)
+#if defined(HAVE_SYS_MMAN_H) && RTS_LINKER_USE_MMAP
 #  include <sys/mman.h>
 #endif
 
@@ -46,6 +46,77 @@
 #define nlist nlist_64
 #endif
 
+/*
+ * Initialize some common data in the object code so we don't have to
+ * continuously look up the addresses.
+ */
+void
+ocInit_MachO(ObjectCode * oc)
+{
+    oc->info = (ObjectCodeFormatInfo*)stgCallocBytes(
+                1, sizeof(ObjectCodeFormatInfo),
+                "ocInit_MachO(ObjectCodeFormatInfo)");
+    oc->info->header  = (MachOHeader *) oc->image;
+    oc->info->symCmd  = NULL;
+    oc->info->segCmd  = NULL;
+    oc->info->dsymCmd = NULL;
+
+    MachOLoadCommand *lc = (MachOLoadCommand*)(oc->image + sizeof(MachOHeader));
+    for(size_t i = 0; i < oc->info->header->ncmds; i++) {
+        if (lc->cmd == LC_SEGMENT || lc->cmd == LC_SEGMENT_64) {
+            oc->info->segCmd = (MachOSegmentCommand*) lc;
+        }
+        else if (lc->cmd == LC_SYMTAB) {
+            oc->info->symCmd = (MachOSymtabCommand*) lc;
+        }
+        else if (lc->cmd == LC_DYSYMTAB) {
+            oc->info->dsymCmd = (MachODsymtabCommand*) lc;
+        }
+        lc = (MachOLoadCommand *) ( ((char*)lc) + lc->cmdsize );
+    }
+    if (NULL == oc->info->segCmd) {
+        barf("ocGetNames_MachO: no segment load command");
+    }
+
+    oc->info->macho_sections = (MachOSection*) (oc->info->segCmd+1);
+    oc->n_sections = oc->info->segCmd->nsects;
+
+    oc->info->nlist = oc->info->symCmd == NULL
+              ? NULL
+              : (MachONList *)(oc->image + oc->info->symCmd->symoff);
+    oc->info->names = oc->image + oc->info->symCmd->stroff;
+
+    /* If we have symbols, allocate and fill the macho_symbols
+     * This will make relocation easier.
+     */
+    oc->info->n_macho_symbols = 0;
+    oc->info->macho_symbols = NULL;
+
+    if(NULL != oc->info->nlist) {
+        oc->info->n_macho_symbols = oc->info->symCmd->nsyms;
+        oc->info->macho_symbols = (MachOSymbol*)stgCallocBytes(
+                                    oc->info->symCmd->nsyms,
+                                    sizeof(MachOSymbol),
+                                    "ocInit_MachO(MachOSymbol)");
+        for(uint32_t i = 0; i < oc->info->symCmd->nsyms; i++) {
+            oc->info->macho_symbols[i].name  = oc->info->names
+                                             + oc->info->nlist[i].n_un.n_strx;
+            oc->info->macho_symbols[i].nlist = &oc->info->nlist[i];
+             /* we don't have an address for this symbol yet; this will be
+              * populated during ocGetNames_MachO. hence addr = NULL
+              */
+            oc->info->macho_symbols[i].addr  = NULL;
+        }
+    }
+}
+
+void
+ocDeinit_MachO(ObjectCode * oc) {
+    if(oc->info->n_macho_symbols > 0) {
+        stgFree(oc->info->macho_symbols);
+    }
+    stgFree(oc->info);
+}
 static int
 resolveImports(
     ObjectCode* oc,
@@ -55,6 +126,7 @@ resolveImports(
     unsigned long *indirectSyms,
     struct nlist *nlist);
 
+#if NEED_SYMBOL_EXTRAS
 #if defined(powerpc_HOST_ARCH)
 int
 ocAllocateSymbolExtras_MachO(ObjectCode* oc)
@@ -144,6 +216,7 @@ ocAllocateSymbolExtras_MachO(ObjectCode* oc)
 #else
 #error Unknown MachO architecture
 #endif /* HOST_ARCH */
+#endif /* NEED_SYMBOL_EXTRAS */
 
 int
 ocVerifyImage_MachO(ObjectCode * oc)
@@ -153,7 +226,7 @@ ocVerifyImage_MachO(ObjectCode * oc)
 
     IF_DEBUG(linker, debugBelch("ocVerifyImage_MachO: start\n"));
 
-#if x86_64_HOST_ARCH || powerpc64_HOST_ARCH
+#if x86_64_HOST_ARCH || powerpc64_HOST_ARCH || aarch64_HOST_ARCH
     if(header->magic != MH_MAGIC_64) {
         errorBelch("Could not load image %s: bad magic!\n"
                    "  Expected %08x (64bit), got %08x%s\n",
@@ -1241,4 +1314,4 @@ machoGetMisalignment( FILE * f )
     return misalignment ? (16 - misalignment) : 0;
 }
 
-#endif /* darwin_HOST_OS */
+#endif /* darwin_HOST_OS, ios_HOST_OS */
diff --git a/rts/linker/MachO.h b/rts/linker/MachO.h
index 8c7fb1f..9362eb7 100644
--- a/rts/linker/MachO.h
+++ b/rts/linker/MachO.h
@@ -5,6 +5,10 @@
 
 #include "BeginPrivate.h"
 
+#include "MachOTypes.h"
+
+void ocInit_MachO          ( ObjectCode* oc );
+void ocDeinit_MachO        ( ObjectCode* oc );
 int ocVerifyImage_MachO    ( ObjectCode* oc );
 int ocGetNames_MachO       ( ObjectCode* oc );
 int ocResolve_MachO        ( ObjectCode* oc );



More information about the ghc-commits mailing list