[commit: ghc] master: Fix system linker on Mac OS X (b32c227)

git at git.haskell.org git at git.haskell.org
Mon Dec 29 16:32:19 UTC 2014


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

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

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

commit b32c22760687a6a1a2e88fdba8de32f6951b5029
Author: Peter Trommler <ptrommler at acm.org>
Date:   Mon Dec 29 11:33:24 2014 -0500

    Fix system linker on Mac OS X
    
    Summary:
    Flag `-l:` is GNU ld specific and not supported by the
    Mac OS X link editor. So we create a temporary file name
    lib<tmpname>.<so_ext> and link with the standard -l<tmpname>
    option on Linux and OS X.
    
    Fixes #9875
    
    Test Plan: validate on Mac OS X
    
    Reviewers: austin, hvr, ezyang
    
    Reviewed By: ezyang
    
    Subscribers: carter, thomie, ezyang
    
    Differential Revision: https://phabricator.haskell.org/D579
    
    GHC Trac Issues: #9875


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

b32c22760687a6a1a2e88fdba8de32f6951b5029
 compiler/ghci/Linker.hs   | 11 +++++------
 compiler/main/SysTools.hs | 20 +++++++++++++++++++-
 2 files changed, 24 insertions(+), 7 deletions(-)

diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs
index 3a91fc1..91706da 100644
--- a/compiler/ghci/Linker.hs
+++ b/compiler/ghci/Linker.hs
@@ -120,7 +120,7 @@ data PersistentLinkerState
 
         -- we need to remember the name of the last temporary DLL/.so
         -- so we can link it
-        last_temp_so :: !(Maybe FilePath) }
+        last_temp_so :: !(Maybe (FilePath, String)) }
 
 
 emptyPLS :: DynFlags -> PersistentLinkerState
@@ -818,7 +818,7 @@ dynLoadObjs :: DynFlags -> PersistentLinkerState -> [FilePath]
 dynLoadObjs _      pls []   = return pls
 dynLoadObjs dflags pls objs = do
     let platform = targetPlatform dflags
-    soFile <- newTempName dflags (soExt platform)
+    (soFile, libPath , libName) <- newTempLibName dflags (soExt platform)
     let -- When running TH for a non-dynamic way, we still need to make
         -- -l flags to link against the dynamic libraries, so we turn
         -- Opt_Static off
@@ -833,12 +833,11 @@ dynLoadObjs dflags pls objs = do
                       ldInputs =
                         case last_temp_so pls of
                           Nothing -> []
-                          Just so  ->
-                                 let (lp, l) = splitFileName so in
+                          Just (lp, l)  ->
                                  [ Option ("-L" ++ lp)
                                  , Option ("-Wl,-rpath")
                                  , Option ("-Wl," ++ lp)
-                                 , Option ("-l:" ++ l)
+                                 , Option ("-l" ++  l)
                                  ],
                       -- Even if we're e.g. profiling, we still want
                       -- the vanilla dynamic libraries, so we set the
@@ -851,7 +850,7 @@ dynLoadObjs dflags pls objs = do
     consIORef (filesToNotIntermediateClean dflags) soFile
     m <- loadDLL soFile
     case m of
-        Nothing -> return pls { last_temp_so = Just soFile }
+        Nothing -> return pls { last_temp_so = Just (libPath, libName) }
         Just err -> panic ("Loading temp shared object failed: " ++ err)
 
 rmDupLinkables :: [Linkable]    -- Already loaded
diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs
index e4520e1..a1209c7 100644
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -40,7 +40,7 @@ module SysTools (
 
         -- Temporary-file management
         setTmpDir,
-        newTempName,
+        newTempName, newTempLibName,
         cleanTempDirs, cleanTempFiles, cleanTempFilesExcept,
         addFilesToClean,
 
@@ -1077,6 +1077,24 @@ newTempName dflags extn
                         consIORef (filesToClean dflags) filename
                         return filename
 
+newTempLibName :: DynFlags -> Suffix -> IO (FilePath, FilePath, String)
+newTempLibName dflags extn
+  = do d <- getTempDir dflags
+       x <- getProcessID
+       findTempName d ("ghc" ++ show x ++ "_")
+  where
+    findTempName :: FilePath -> String -> IO (FilePath, FilePath, String)
+    findTempName dir prefix
+      = do n <- newTempSuffix dflags
+           let libname = prefix ++ show n
+               filename = dir </> "lib" ++ libname <.> extn
+           b <- doesFileExist filename
+           if b then findTempName dir prefix
+                else do -- clean it up later
+                        consIORef (filesToClean dflags) filename
+                        return (filename, dir, libname)
+
+
 -- Return our temporary directory within tmp_dir, creating one if we
 -- don't have one yet.
 getTempDir :: DynFlags -> IO FilePath



More information about the ghc-commits mailing list