summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMoritz Angermann <moritz.angermann@iohk.io>2020-08-13 12:26:41 +0800
committerMoritz Angermann <moritz.angermann@iohk.io>2020-09-11 13:19:37 +0800
commit3ebc51e667d3b41735f28eee7a63058989765009 (patch)
treef41bbec244024c7b75678af3c3ff938a21006ef2
parentd6cbfd9a29452b3d4d0ccf17f0f68e472842b6e9 (diff)
downloadhaskell-wip/angerman/ghc-8.8-backport-rpath.tar.gz
[macOS] improved runpath handlingwip/angerman/ghc-8.8-backport-rpath
In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) (cherry picked from commit 4ff93292243888545da452ea4d4c1987f2343591) Signed-off-by: Moritz Angermann <moritz.angermann@iohk.io>
-rw-r--r--aclocal.m414
-rw-r--r--compiler/ghci/Linker.hs30
-rw-r--r--compiler/main/DriverPipeline.hs66
-rw-r--r--compiler/main/DynFlags.hs35
-rw-r--r--compiler/main/SysTools.hs18
-rw-r--r--compiler/main/SysTools/Tasks.hs48
-rw-r--r--configure.ac14
-rw-r--r--docs/users_guide/phases.rst18
-rw-r--r--includes/ghc.mk3
-rw-r--r--settings.in3
10 files changed, 224 insertions, 25 deletions
diff --git a/aclocal.m4 b/aclocal.m4
index 41cecf098b..ca76fc5f31 100644
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -566,6 +566,18 @@ AC_DEFUN([FP_SETTINGS],
else
SettingsOptCommand="$OptCmd"
fi
+ if test -z "$OtoolCmd"
+ then
+ SettingsOtoolCommand="otool"
+ else
+ SettingsOtoolCommand="$OtoolCmd"
+ fi
+ if test -z "$InstallNameToolCmd"
+ then
+ SettingsInstallNameToolCommand="install_name_tool"
+ else
+ SettingsInstallNameToolCommand="$InstallNameToolCmd"
+ fi
SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE"
@@ -581,6 +593,8 @@ AC_DEFUN([FP_SETTINGS],
AC_SUBST(SettingsArCommand)
AC_SUBST(SettingsRanlibCommand)
AC_SUBST(SettingsPerlCommand)
+ AC_SUBST(SettingsOtoolCommand)
+ AC_SUBST(SettingsInstallNameToolCommand)
AC_SUBST(SettingsDllWrapCommand)
AC_SUBST(SettingsWindresCommand)
AC_SUBST(SettingsLibtoolCommand)
diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs
index 41cc218e12..dbe71cd9ab 100644
--- a/compiler/ghci/Linker.hs
+++ b/compiler/ghci/Linker.hs
@@ -945,20 +945,26 @@ dynLoadObjs hsc_env pls objs = do
ldInputs =
concatMap (\l -> [ Option ("-l" ++ l) ])
(nub $ snd <$> temp_sos pls)
- ++ 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 pls)
++ 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/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index bf79ea5d02..a64179eded 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -366,7 +366,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?
@@ -1888,9 +1937,12 @@ linkBinary' staticLink dflags o_files dep_packages = do
rc_objs <- maybeCreateManifest dflags output_fn
- let link = if staticLink
- then SysTools.runLibtool
- else SysTools.runLink
+ let link dflags args | staticLink = SysTools.runLibtool dflags args
+ | platformOS platform == OSDarwin
+ = SysTools.runLink dflags args >> SysTools.runInjectRPaths dflags pkg_lib_paths output_fn
+ | otherwise
+ = SysTools.runLink dflags args
+
link dflags (
map SysTools.Option verbFlags
++ [ SysTools.Option "-o"
@@ -1959,7 +2011,11 @@ linkBinary' staticLink dflags o_files dep_packages = do
++ debug_opts
++ thread_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 in the runInjectRpaths phase below.
+ then [ "-Wl,-dead_strip_dylibs", "-Wl,-headerpad,8000" ]
else [])
))
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index a7ec70f876..ef12d917a2 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -92,7 +92,8 @@ module DynFlags (
extraGccViaCFlags, systemPackageConfig,
pgm_L, pgm_P, pgm_F, pgm_c, pgm_s, pgm_a, pgm_l, pgm_dll, pgm_T,
pgm_windres, pgm_libtool, pgm_ar, pgm_ranlib, pgm_lo, pgm_lc,
- pgm_lcc, pgm_i, opt_L, opt_P, opt_F, opt_c, opt_a, opt_l, opt_i,
+ pgm_lcc, pgm_i, pgm_otool, pgm_install_name_tool, opt_L, opt_P,
+ opt_F, opt_c, opt_a, opt_l, opt_i,
opt_P_signature,
opt_windres, opt_lo, opt_lc, opt_lcc,
@@ -1323,6 +1324,8 @@ data Settings = Settings {
sPgm_windres :: String,
sPgm_libtool :: String,
sPgm_ar :: String,
+ sPgm_otool :: String,
+ sPgm_install_name_tool :: String,
sPgm_ranlib :: String,
sPgm_lo :: (String,[Option]), -- LLVM: opt llvm optimiser
sPgm_lc :: (String,[Option]), -- LLVM: llc static compiler
@@ -1394,6 +1397,10 @@ pgm_lcc :: DynFlags -> (String,[Option])
pgm_lcc dflags = sPgm_lcc (settings dflags)
pgm_ar :: DynFlags -> String
pgm_ar dflags = sPgm_ar (settings dflags)
+pgm_otool :: DynFlags -> String
+pgm_otool dflags = sPgm_otool (settings dflags)
+pgm_install_name_tool :: DynFlags -> String
+pgm_install_name_tool dflags = sPgm_install_name_tool (settings dflags)
pgm_ranlib :: DynFlags -> String
pgm_ranlib dflags = sPgm_ranlib (settings dflags)
pgm_lo :: DynFlags -> (String,[Option])
@@ -3020,7 +3027,10 @@ dynamic_flags_deps = [
(hasArg (\f -> alterSettings (\s -> s { sPgm_ar = f})))
, make_ord_flag defFlag "pgmranlib"
(hasArg (\f -> alterSettings (\s -> s { sPgm_ranlib = f})))
-
+ , make_ord_flag defFlag "pgmotool"
+ (hasArg (\f -> alterSettings (\s -> s { sPgm_otool = f})))
+ , make_ord_flag defFlag "pgminstall_name_tool"
+ (hasArg (\f -> alterSettings (\s -> s { sPgm_install_name_tool = f})))
-- need to appear before -optl/-opta to be parsed as LLVM flags.
, make_ord_flag defFlag "optlo"
@@ -4468,7 +4478,6 @@ defaultFlags settings
Opt_OmitYields,
Opt_PrintBindContents,
Opt_ProfCountEntries,
- Opt_RPath,
Opt_SharedImplib,
Opt_SimplPreInlining,
Opt_VersionMacros
@@ -4479,6 +4488,8 @@ defaultFlags settings
++ default_PIC platform
+ ++ default_RPath platform
+
++ concatMap (wayGeneralFlags platform) (defaultWays settings)
++ validHoleFitDefaults
@@ -4519,6 +4530,24 @@ default_PIC platform =
-- information.
_ -> []
+-- We usually want to use RPath, except on macOS (OSDarwin). On recent macOS
+-- version the number of load commands we can embed in a dynamic library are
+-- 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.
+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/main/SysTools.hs b/compiler/main/SysTools.hs
index 9bbce19602..63103a3bac 100644
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -229,6 +229,8 @@ initSysTools top_dir
libtool_path <- getToolSetting "libtool command"
ar_path <- getToolSetting "ar command"
ranlib_path <- getToolSetting "ranlib command"
+ otool_path <- getToolSetting "otool command"
+ install_name_tool_path <- getToolSetting "install_name_tool command"
tmpdir <- getTemporaryDirectory
@@ -306,6 +308,8 @@ initSysTools top_dir
sPgm_libtool = libtool_path,
sPgm_ar = ar_path,
sPgm_ranlib = ranlib_path,
+ sPgm_otool = otool_path,
+ sPgm_install_name_tool = install_name_tool_path,
sPgm_lo = (lo_prog,[]),
sPgm_lc = (lc_prog,[]),
sPgm_lcc = (lcc_prog,[]),
@@ -415,7 +419,10 @@ linkDynLib dflags0 o_files dep_packages
| ( osElfTarget (platformOS (targetPlatform dflags)) ||
osMachOTarget (platformOS (targetPlatform dflags)) ) &&
dynLibLoader dflags == SystemDependent &&
- WayDyn `elem` ways dflags
+ -- Only if we want dynamic libraries
+ WayDyn `elem` 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]
@@ -538,8 +545,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/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs
index 45ca73bcf9..ba957b2e86 100644
--- a/compiler/main/SysTools/Tasks.hs
+++ b/compiler/main/SysTools/Tasks.hs
@@ -26,6 +26,10 @@ import LlvmCodeGen.Base (LlvmVersion, llvmVersionStr, supportedLlvmVersion, pars
import SysTools.Process
import SysTools.Info
+import Control.Monad (join, forM, filterM)
+import System.Directory (doesFileExist)
+import System.FilePath ((</>))
+
{-
************************************************************************
* *
@@ -220,6 +224,39 @@ figureLlvmVersion dflags = do
llvmVersionStr supportedLlvmVersion) ]
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 = do
@@ -301,6 +338,17 @@ askAr dflags mb_cwd args = do
runSomethingWith dflags "Ar" ar args $ \real_args ->
readCreateProcessWithExitCode' (proc ar real_args){ cwd = mb_cwd }
+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 = do
let ranlib = pgm_ranlib dflags
diff --git a/configure.ac b/configure.ac
index cc52b29dd6..a7fd3b5155 100644
--- a/configure.ac
+++ b/configure.ac
@@ -651,6 +651,18 @@ else
fi
AC_SUBST([LibtoolCmd])
+dnl ** Which otool to use on macOS
+dnl --------------------------------------------------------------
+AC_CHECK_TARGET_TOOL([OTOOL], [otool])
+OtoolCmd="$OTOOL"
+AC_SUBST(OtoolCmd)
+
+dnl ** Which install_name_tool to use on macOS
+dnl --------------------------------------------------------------
+AC_CHECK_TARGET_TOOL([INSTALL_NAME_TOOL], [install_name_tool])
+InstallNameToolCmd="$INSTALL_NAME_TOOL"
+AC_SUBST(InstallNameToolCmd)
+
# Here is where we re-target which specific version of the LLVM
# tools we are looking for. In the past, GHC supported a number of
# versions of LLVM simultaneously, but that stopped working around
@@ -1413,6 +1425,8 @@ echo "\
libtool : $LibtoolCmd
objdump : $ObjdumpCmd
ranlib : $RanlibCmd
+ otool : $OtoolCmd
+ install_name_tool : $InstallNameToolCmd
windres : $WindresCmd
dllwrap : $DllWrapCmd
genlib : $GenlibCmd
diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst
index f5f735b81b..f32a07630d 100644
--- a/docs/users_guide/phases.rst
+++ b/docs/users_guide/phases.rst
@@ -87,6 +87,24 @@ given compilation phase:
Use ⟨cmd⟩ as the pre-processor (with ``-F`` only).
+.. ghc-flag:: -pgmotool ⟨cmd⟩
+ :shortdesc: Use ⟨cmd⟩ as the program to inspect mach-o dylibs on macOS
+ :type: dynamic
+ :category: phase-programs
+
+ Use ⟨cmd⟩ as the program to inspect mach-o dynamic libraries and
+ executables to read the dynamic library dependencies. We will compute
+ the necessary ``runpath``s to embed for the dependencies based on the
+ result of the ``otool`` call.
+
+.. ghc-flag:: -pgminstall_name_tool ⟨cmd⟩
+ :shortdesc: Use ⟨cmd⟩ as the program to inject ``runpath`` into mach-o dylibs on macOS
+ :type: dynamic
+ :category: phase-programs
+
+ Use ⟨cmd⟩ as the program to inject ``runpath``s into mach-o dynamic
+ libraries and executables. As detected by the ``otool`` call.
+
.. ghc-flag:: -pgmwindres ⟨cmd⟩
:shortdesc: Use ⟨cmd⟩ as the program for embedding manifests on Windows.
:type: dynamic
diff --git a/includes/ghc.mk b/includes/ghc.mk
index d08ecfbc07..47fbb0d899 100644
--- a/includes/ghc.mk
+++ b/includes/ghc.mk
@@ -154,7 +154,7 @@ $(includes_H_PLATFORM) : includes/Makefile | $$(dir $$@)/.
@echo "#define $(TargetPlatform_CPP)_TARGET 1" >> $@
@echo "#define $(TargetArch_CPP)_TARGET_ARCH 1" >> $@
@echo "#define TARGET_ARCH \"$(TargetArch_CPP)\"" >> $@
- @echo "#define $(TargetOS_CPP)_TARGET_OS 1" >> $@
+ @echo "#define $(TargetOS_CPP)_TARGET_OS 1" >> $@
@echo "#define TARGET_OS \"$(TargetOS_CPP)\"" >> $@
@echo "#define $(TargetVendor_CPP)_TARGET_VENDOR 1" >> $@
ifeq "$(GhcUnregisterised)" "YES"
@@ -229,4 +229,3 @@ install_includes :
$(INSTALL_HEADER) $(INSTALL_OPTS) includes/$d/*.h "$(DESTDIR)$(ghcheaderdir)/$d/" && \
) true
$(INSTALL_HEADER) $(INSTALL_OPTS) $(includes_H_CONFIG) $(includes_H_PLATFORM) $(includes_H_VERSION) $(includes_DERIVEDCONSTANTS) "$(DESTDIR)$(ghcheaderdir)/"
-
diff --git a/settings.in b/settings.in
index 30bfe7072b..9fde7d39c2 100644
--- a/settings.in
+++ b/settings.in
@@ -15,6 +15,8 @@
("ar flags", "@ArArgs@"),
("ar supports at file", "@ArSupportsAtFile@"),
("ranlib command", "@SettingsRanlibCommand@"),
+ ("otool command", "@SettingsOtoolCommand@"),
+ ("install_name_tool command", "@SettingsInstallNameToolCommand@"),
("touch command", "@SettingsTouchCommand@"),
("dllwrap command", "@SettingsDllWrapCommand@"),
("windres command", "@SettingsWindresCommand@"),
@@ -33,4 +35,3 @@
("LLVM opt command", "@SettingsOptCommand@"),
("LLVM clang command", "@SettingsClangCommand@")
]
-