summaryrefslogtreecommitdiff
path: root/compiler/GHC
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC')
-rw-r--r--compiler/GHC/Driver/Pipeline.hs68
-rw-r--r--compiler/GHC/Driver/Session.hs38
-rw-r--r--compiler/GHC/Runtime/Linker.hs26
-rw-r--r--compiler/GHC/Settings.hs8
-rw-r--r--compiler/GHC/Settings/IO.hs4
-rw-r--r--compiler/GHC/SysTools.hs14
-rw-r--r--compiler/GHC/SysTools/Tasks.hs50
7 files changed, 186 insertions, 22 deletions
diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs
index d960cd95f8..d13bf11c56 100644
--- a/compiler/GHC/Driver/Pipeline.hs
+++ b/compiler/GHC/Driver/Pipeline.hs
@@ -391,7 +391,56 @@ compileEmptyStub dflags hsc_env basename location mod_name = do
-- ---------------------------------------------------------------------------
-- Link
-
+--
+-- Note [Dynamic linking on macOS]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
+-- Since macOS Sierra (10.14), the dynamic system linker enforces
+-- a limit on the Load Commands. Specifically the Load Command Size
+-- Limit is at 32K (32768). The Load Commands contain the install
+-- name, dependencies, runpaths, and a few other commands. We however
+-- only have control over the install name, dependencies and runpaths.
+--
+-- The install name is the name by which this library will be
+-- referenced. This is such that we do not need to bake in the full
+-- absolute location of the library, and can move the library around.
+--
+-- The dependency commands contain the install names from of referenced
+-- libraries. Thus if a libraries install name is @rpath/libHS...dylib,
+-- that will end up as the dependency.
+--
+-- Finally we have the runpaths, which informs the linker about the
+-- directories to search for the referenced dependencies.
+--
+-- The system linker can do recursive linking, however using only the
+-- direct dependencies conflicts with ghc's ability to inline across
+-- packages, and as such would end up with unresolved symbols.
+--
+-- Thus we will pass the full dependency closure to the linker, and then
+-- ask the linker to remove any unused dynamic libraries (-dead_strip_dylibs).
+--
+-- We still need to add the relevant runpaths, for the dynamic linker to
+-- lookup the referenced libraries though. The linker (ld64) does not
+-- have any option to dead strip runpaths; which makes sense as runpaths
+-- can be used for dependencies of dependencies as well.
+--
+-- The solution we then take in GHC is to not pass any runpaths to the
+-- linker at link time, but inject them after the linking. For this to
+-- work we'll need to ask the linker to create enough space in the header
+-- to add more runpaths after the linking (-headerpad 8000).
+--
+-- After the library has been linked by $LD (usually ld64), we will use
+-- otool to inspect the libraries left over after dead stripping, compute
+-- the relevant runpaths, and inject them into the linked product using
+-- the install_name_tool command.
+--
+-- This strategy should produce the smallest possible set of load commands
+-- while still retaining some form of relocatability via runpaths.
+--
+-- The only way I can see to reduce the load command size further would be
+-- by shortening the library names, or start putting libraries into the same
+-- folders, such that one runpath would be sufficient for multiple/all
+-- libraries.
link :: GhcLink -- interactive or batch
-> DynFlags -- dynamic flags
-> Bool -- attempt linking in batch mode?
@@ -1766,9 +1815,12 @@ linkBinary' staticLink dflags o_files dep_units = do
rc_objs <- maybeCreateManifest dflags output_fn
- let link = if staticLink
- then GHC.SysTools.runLibtool
- else GHC.SysTools.runLink
+ let link dflags args | staticLink = GHC.SysTools.runLibtool dflags args
+ | platformOS platform == OSDarwin
+ = GHC.SysTools.runLink dflags args >> GHC.SysTools.runInjectRPaths dflags pkg_lib_paths output_fn
+ | otherwise
+ = GHC.SysTools.runLink dflags args
+
link dflags (
map GHC.SysTools.Option verbFlags
++ [ GHC.SysTools.Option "-o"
@@ -1835,7 +1887,13 @@ linkBinary' staticLink dflags o_files dep_units = do
++ pkg_link_opts
++ pkg_framework_opts
++ (if platformOS platform == OSDarwin
- then [ "-Wl,-dead_strip_dylibs" ]
+ -- dead_strip_dylibs, will remove unused dylibs, and thus save
+ -- space in the load commands. The -headerpad is necessary so
+ -- that we can inject more @rpath's later for the left over
+ -- libraries during runInjectRpaths phase.
+ --
+ -- See Note [Dynamic linking on macOS].
+ then [ "-Wl,-dead_strip_dylibs", "-Wl,-headerpad,8000" ]
else [])
))
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index 5614894e0c..83063a5f71 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -147,8 +147,8 @@ module GHC.Driver.Session (
versionedAppDir, versionedFilePath,
extraGccViaCFlags, globalPackageDatabasePath,
pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T,
- pgm_windres, pgm_libtool, pgm_ar, pgm_ranlib, pgm_lo, pgm_lc,
- pgm_lcc, pgm_i,
+ pgm_windres, pgm_libtool, pgm_ar, pgm_otool, pgm_install_name_tool,
+ pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i,
opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i,
opt_P_signature,
opt_windres, opt_lo, opt_lc, opt_lcc,
@@ -950,6 +950,10 @@ pgm_lcc :: DynFlags -> (String,[Option])
pgm_lcc dflags = toolSettings_pgm_lcc $ toolSettings dflags
pgm_ar :: DynFlags -> String
pgm_ar dflags = toolSettings_pgm_ar $ toolSettings dflags
+pgm_otool :: DynFlags -> String
+pgm_otool dflags = toolSettings_pgm_otool $ toolSettings dflags
+pgm_install_name_tool :: DynFlags -> String
+pgm_install_name_tool dflags = toolSettings_pgm_install_name_tool $ toolSettings dflags
pgm_ranlib :: DynFlags -> String
pgm_ranlib dflags = toolSettings_pgm_ranlib $ toolSettings dflags
pgm_lo :: DynFlags -> (String,[Option])
@@ -2393,6 +2397,10 @@ dynamic_flags_deps = [
$ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_libtool = f }
, make_ord_flag defFlag "pgmar"
$ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ar = f }
+ , make_ord_flag defFlag "pgmotool"
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_otool = f}
+ , make_ord_flag defFlag "pgminstall_name_tool"
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_install_name_tool = f}
, make_ord_flag defFlag "pgmranlib"
$ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ranlib = f }
@@ -3903,7 +3911,6 @@ defaultFlags settings
Opt_OmitYields,
Opt_PrintBindContents,
Opt_ProfCountEntries,
- Opt_RPath,
Opt_SharedImplib,
Opt_SimplPreInlining,
Opt_VersionMacros
@@ -3914,6 +3921,8 @@ defaultFlags settings
++ default_PIC platform
+ ++ default_RPath platform
+
++ concatMap (wayGeneralFlags platform) (defaultWays settings)
++ validHoleFitDefaults
@@ -3954,6 +3963,29 @@ default_PIC platform =
-- information.
_ -> []
+
+-- We usually want to use RPath, except on macOS (OSDarwin). On recent macOS
+-- versions the number of load commands we can embed in a dynamic library is
+-- restricted. Hence since b592bd98ff2 we rely on -dead_strip_dylib to only
+-- link the needed dylibs instead of linking the full dependency closure.
+--
+-- If we split the library linking into injecting -rpath and -l @rpath/...
+-- components, we will reduce the number of libraries we link, however we will
+-- still inject one -rpath entry for each library, independent of their use.
+-- That is, we even inject -rpath values for libraries that we dead_strip in
+-- the end. As such we can run afoul of the load command size limit simply
+-- by polluting the load commands with RPATH entries.
+--
+-- Thus, we disable Opt_RPath by default on OSDarwin. The savvy user can always
+-- enable it with -use-rpath if they so wish.
+--
+-- See Note [Dynamic linking on macOS]
+
+default_RPath :: Platform -> [GeneralFlag]
+default_RPath platform | platformOS platform == OSDarwin = []
+default_RPath _ = [Opt_RPath]
+
+
-- General flags that are switched on/off when other general flags are switched
-- on
impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
diff --git a/compiler/GHC/Runtime/Linker.hs b/compiler/GHC/Runtime/Linker.hs
index 896eaea581..c6dcea05ba 100644
--- a/compiler/GHC/Runtime/Linker.hs
+++ b/compiler/GHC/Runtime/Linker.hs
@@ -927,20 +927,22 @@ dynLoadObjs hsc_env pls@PersistentLinkerState{..} objs = do
ldInputs =
concatMap (\l -> [ Option ("-l" ++ l) ])
(nub $ snd <$> temp_sos)
- ++ concatMap (\lp -> [ Option ("-L" ++ lp)
- , Option "-Xlinker"
- , Option "-rpath"
- , Option "-Xlinker"
- , Option lp ])
+ ++ concatMap (\lp -> Option ("-L" ++ lp)
+ : if gopt Opt_RPath dflags
+ then [ Option "-Xlinker"
+ , Option "-rpath"
+ , Option "-Xlinker"
+ , Option lp ]
+ else [])
(nub $ fst <$> temp_sos)
++ concatMap
- (\lp ->
- [ Option ("-L" ++ lp)
- , Option "-Xlinker"
- , Option "-rpath"
- , Option "-Xlinker"
- , Option lp
- ])
+ (\lp -> Option ("-L" ++ lp)
+ : if gopt Opt_RPath dflags
+ then [ Option "-Xlinker"
+ , Option "-rpath"
+ , Option "-Xlinker"
+ , Option lp ]
+ else [])
minus_big_ls
-- See Note [-Xlinker -rpath vs -Wl,-rpath]
++ map (\l -> Option ("-l" ++ l)) minus_ls,
diff --git a/compiler/GHC/Settings.hs b/compiler/GHC/Settings.hs
index eed7288991..7a0e4ddaaa 100644
--- a/compiler/GHC/Settings.hs
+++ b/compiler/GHC/Settings.hs
@@ -36,6 +36,8 @@ module GHC.Settings
, sPgm_windres
, sPgm_libtool
, sPgm_ar
+ , sPgm_otool
+ , sPgm_install_name_tool
, sPgm_ranlib
, sPgm_lo
, sPgm_lc
@@ -109,6 +111,8 @@ data ToolSettings = ToolSettings
, toolSettings_pgm_windres :: String
, toolSettings_pgm_libtool :: String
, toolSettings_pgm_ar :: String
+ , toolSettings_pgm_otool :: String
+ , toolSettings_pgm_install_name_tool :: String
, toolSettings_pgm_ranlib :: String
, -- | LLVM: opt llvm optimiser
toolSettings_pgm_lo :: (String, [Option])
@@ -222,6 +226,10 @@ sPgm_libtool :: Settings -> String
sPgm_libtool = toolSettings_pgm_libtool . sToolSettings
sPgm_ar :: Settings -> String
sPgm_ar = toolSettings_pgm_ar . sToolSettings
+sPgm_otool :: Settings -> String
+sPgm_otool = toolSettings_pgm_otool . sToolSettings
+sPgm_install_name_tool :: Settings -> String
+sPgm_install_name_tool = toolSettings_pgm_install_name_tool . sToolSettings
sPgm_ranlib :: Settings -> String
sPgm_ranlib = toolSettings_pgm_ranlib . sToolSettings
sPgm_lo :: Settings -> (String, [Option])
diff --git a/compiler/GHC/Settings/IO.hs b/compiler/GHC/Settings/IO.hs
index 75f0bcca0e..8bb561ad52 100644
--- a/compiler/GHC/Settings/IO.hs
+++ b/compiler/GHC/Settings/IO.hs
@@ -116,6 +116,8 @@ initSettings top_dir = do
windres_path <- getToolSetting "windres command"
libtool_path <- getToolSetting "libtool command"
ar_path <- getToolSetting "ar command"
+ otool_path <- getToolSetting "otool command"
+ install_name_tool_path <- getToolSetting "install_name_tool command"
ranlib_path <- getToolSetting "ranlib command"
-- TODO this side-effect doesn't belong here. Reading and parsing the settings
@@ -192,6 +194,8 @@ initSettings top_dir = do
, toolSettings_pgm_windres = windres_path
, toolSettings_pgm_libtool = libtool_path
, toolSettings_pgm_ar = ar_path
+ , toolSettings_pgm_otool = otool_path
+ , toolSettings_pgm_install_name_tool = install_name_tool_path
, toolSettings_pgm_ranlib = ranlib_path
, toolSettings_pgm_lo = (lo_prog,[])
, toolSettings_pgm_lc = (lc_prog,[])
diff --git a/compiler/GHC/SysTools.hs b/compiler/GHC/SysTools.hs
index 0b71e8ccde..3ad3ca08ba 100644
--- a/compiler/GHC/SysTools.hs
+++ b/compiler/GHC/SysTools.hs
@@ -254,7 +254,10 @@ linkDynLib dflags0 o_files dep_packages
| ( osElfTarget (platformOS (targetPlatform dflags)) ||
osMachOTarget (platformOS (targetPlatform dflags)) ) &&
dynLibLoader dflags == SystemDependent &&
- WayDyn `Set.member` ways dflags
+ -- Only if we want dynamic libraries
+ WayDyn `Set.member` ways dflags &&
+ -- Only use RPath if we explicitly asked for it
+ gopt Opt_RPath dflags
= ["-L" ++ l, "-Xlinker", "-rpath", "-Xlinker", l]
-- See Note [-Xlinker -rpath vs -Wl,-rpath]
| otherwise = ["-L" ++ l]
@@ -379,8 +382,15 @@ linkDynLib dflags0 o_files dep_packages
++ map Option pkg_lib_path_opts
++ map Option pkg_link_opts
++ map Option pkg_framework_opts
- ++ [ Option "-Wl,-dead_strip_dylibs" ]
+ -- dead_strip_dylibs, will remove unused dylibs, and thus save
+ -- space in the load commands. The -headerpad is necessary so
+ -- that we can inject more @rpath's later for the leftover
+ -- libraries in the runInjectRpaths phase below.
+ --
+ -- See Note [Dynamic linking on macOS]
+ ++ [ Option "-Wl,-dead_strip_dylibs", Option "-Wl,-headerpad,8000" ]
)
+ runInjectRPaths dflags pkg_lib_paths output_fn
_ -> do
-------------------------------------------------------------------
-- Making a DSO
diff --git a/compiler/GHC/SysTools/Tasks.hs b/compiler/GHC/SysTools/Tasks.hs
index f9962284f9..7dc40cef04 100644
--- a/compiler/GHC/SysTools/Tasks.hs
+++ b/compiler/GHC/SysTools/Tasks.hs
@@ -28,6 +28,10 @@ import GHC.CmmToLlvm.Base (LlvmVersion, llvmVersionStr, supportedLlvmVersion, pa
import GHC.SysTools.Process
import GHC.SysTools.Info
+import Control.Monad (join, forM, filterM)
+import System.Directory (doesFileExist)
+import System.FilePath ((</>))
+
{-
************************************************************************
* *
@@ -237,6 +241,41 @@ figureLlvmVersion dflags = traceToolCommand dflags "llc" $ do
return Nothing)
+-- | On macOS we rely on the linkers @-dead_strip_dylibs@ flag to remove unused
+-- libraries from the dynamic library. We do this to reduce the number of load
+-- commands that end up in the dylib, and has been limited to 32K (32768) since
+-- macOS Sierra (10.14).
+--
+-- @-dead_strip_dylibs@ does not dead strip @-rpath@ entries, as such passing
+-- @-l@ and @-rpath@ to the linker will result in the unnecesasry libraries not
+-- being included in the load commands, however the @-rpath@ entries are all
+-- forced to be included. This can lead to 100s of @-rpath@ entries being
+-- included when only a handful of libraries end up being truely linked.
+--
+-- Thus after building the library, we run a fixup phase where we inject the
+-- @-rpath@ for each found library (in the given library search paths) into the
+-- dynamic library through @-add_rpath@.
+--
+-- See Note [Dynamic linking on macOS]
+runInjectRPaths :: DynFlags -> [FilePath] -> FilePath -> IO ()
+runInjectRPaths dflags lib_paths dylib = do
+ info <- lines <$> askOtool dflags Nothing [Option "-L", Option dylib]
+ -- filter the output for only the libraries. And then drop the @rpath prefix.
+ let libs = fmap (drop 7) $ filter (isPrefixOf "@rpath") $ fmap (head.words) $ info
+ -- find any pre-existing LC_PATH items
+ info <- fmap words.lines <$> askOtool dflags Nothing [Option "-l", Option dylib]
+ let paths = concatMap f info
+ where f ("path":p:_) = [p]
+ f _ = []
+ lib_paths' = [ p | p <- lib_paths, not (p `elem` paths) ]
+ -- only find those rpaths, that aren't already in the library.
+ rpaths <- nub.sort.join <$> forM libs (\f -> filterM (\l -> doesFileExist (l </> f)) lib_paths')
+ -- inject the rpaths
+ case rpaths of
+ [] -> return ()
+ _ -> runInstallNameTool dflags $ map Option $ "-add_rpath":(intersperse "-add_rpath" rpaths) ++ [dylib]
+
+
runLink :: DynFlags -> [Option] -> IO ()
runLink dflags args = traceToolCommand dflags "linker" $ do
-- See Note [Run-time linker info]
@@ -329,6 +368,17 @@ runAr dflags cwd args = traceToolCommand dflags "ar" $ do
let ar = pgm_ar dflags
runSomethingFiltered dflags id "Ar" ar args cwd Nothing
+askOtool :: DynFlags -> Maybe FilePath -> [Option] -> IO String
+askOtool dflags mb_cwd args = do
+ let otool = pgm_otool dflags
+ runSomethingWith dflags "otool" otool args $ \real_args ->
+ readCreateProcessWithExitCode' (proc otool real_args){ cwd = mb_cwd }
+
+runInstallNameTool :: DynFlags -> [Option] -> IO ()
+runInstallNameTool dflags args = do
+ let tool = pgm_install_name_tool dflags
+ runSomethingFiltered dflags id "Install Name Tool" tool args Nothing Nothing
+
runRanlib :: DynFlags -> [Option] -> IO ()
runRanlib dflags args = traceToolCommand dflags "ranlib" $ do
let ranlib = pgm_ranlib dflags