diff --git a/aclocal.m4 b/aclocal.m4
index 78ce4ea9f36f7d395cd8f5c869e352befce79e50..9cdc20e524ecc32d804ba7ad3860ddee20e65f47 100644
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -579,6 +579,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"
     SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
     SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
@@ -596,6 +608,8 @@ AC_DEFUN([FP_SETTINGS],
     AC_SUBST(SettingsLdFlags)
     AC_SUBST(SettingsArCommand)
     AC_SUBST(SettingsRanlibCommand)
+    AC_SUBST(SettingsOtoolCommand)
+    AC_SUBST(SettingsInstallNameToolCommand)
     AC_SUBST(SettingsDllWrapCommand)
     AC_SUBST(SettingsWindresCommand)
     AC_SUBST(SettingsLibtoolCommand)
diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs
index 8386dd9c7ea767ab42ebb8a2f8b44c6c9cf6fba6..7276762f0ffa14ea706402f8ce2277550205d9fd 100644
--- a/compiler/GHC/Driver/Pipeline.hs
+++ b/compiler/GHC/Driver/Pipeline.hs
@@ -394,7 +394,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?
@@ -1787,9 +1836,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"
@@ -1856,7 +1908,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 041c7bc4184c1a99cd37327b20f4e9c11588f57f..a0c2331d536389a6fb1399fb0597f6093143d9c2 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -145,8 +145,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,
@@ -885,6 +885,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])
@@ -2267,6 +2271,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 }
 
@@ -3780,7 +3788,6 @@ defaultFlags settings
       Opt_OmitYields,
       Opt_PrintBindContents,
       Opt_ProfCountEntries,
-      Opt_RPath,
       Opt_SharedImplib,
       Opt_SimplPreInlining,
       Opt_VersionMacros
@@ -3791,6 +3798,8 @@ defaultFlags settings
 
     ++ default_PIC platform
 
+    ++ default_RPath platform
+
     ++ concatMap (wayGeneralFlags platform) (defaultWays settings)
     ++ validHoleFitDefaults
 
@@ -3831,6 +3840,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 4a3b03e5ebc45515c551f2a4c653ef5c2aed562c..820489671ff6c77e414845ea83ad2427894e60a5 100644
--- a/compiler/GHC/Runtime/Linker.hs
+++ b/compiler/GHC/Runtime/Linker.hs
@@ -929,20 +929,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 e698f47dea744ae95908d25c84ebb95fdb82a62e..8258cb1d72f1792f913282dda592e82d93ef4eab 100644
--- a/compiler/GHC/Settings.hs
+++ b/compiler/GHC/Settings.hs
@@ -34,6 +34,8 @@ module GHC.Settings
   , sPgm_windres
   , sPgm_libtool
   , sPgm_ar
+  , sPgm_otool
+  , sPgm_install_name_tool
   , sPgm_ranlib
   , sPgm_lo
   , sPgm_lc
@@ -107,6 +109,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])
@@ -216,6 +220,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 b5defa0ee28161c838bba264712bf61c8bf94397..73abcf2a4474071c4dd326b3316e785fa6069ad8 100644
--- a/compiler/GHC/Settings/IO.hs
+++ b/compiler/GHC/Settings/IO.hs
@@ -115,6 +115,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
@@ -191,6 +193,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 f3b4f4cc874e0f0bfbac04ee6600e5c1afaa85f5..28531c17a82e71bdb02d01fc23de544685dff5f4 100644
--- a/compiler/GHC/SysTools.hs
+++ b/compiler/GHC/SysTools.hs
@@ -259,7 +259,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]
@@ -384,8 +387,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 f9962284f9149cf461fafc810b04e93a955ecf18..b3ef7251d25bc995d730158701265d415ccb8bec 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
diff --git a/configure.ac b/configure.ac
index 5e3dfa5470435939ca8cdd4e8eba8e0466e9df1e..cc7a0cd77235da64ec470dfe5c74c57a1fe2fe5b 100644
--- a/configure.ac
+++ b/configure.ac
@@ -697,6 +697,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
@@ -1520,6 +1532,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 3c94a39733d5fed56981032519cbee8ebf7e2287..4b7c8c72ef23f3c4e76f83362f1181ec1804a78c 100644
--- a/docs/users_guide/phases.rst
+++ b/docs/users_guide/phases.rst
@@ -95,6 +95,24 @@ given compilation phase:
 
     Use ⟨cmd⟩ as the pre-processor (with :ghc-flag:`-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/hadrian/cfg/system.config.in b/hadrian/cfg/system.config.in
index 5abcb96b7e8036f1972e0e921c7651dbc6604df7..4b3f86d4917712be6bffcfb504d1e61a2c761779 100644
--- a/hadrian/cfg/system.config.in
+++ b/hadrian/cfg/system.config.in
@@ -151,6 +151,8 @@ settings-merge-objects-command = @SettingsMergeObjectsCommand@
 settings-merge-objects-flags = @SettingsMergeObjectsFlags@
 settings-ar-command = @SettingsArCommand@
 settings-ranlib-command = @SettingsRanlibCommand@
+settings-otool-command = @SettingsOtoolCommand@
+settings-install_name_tool-command = @SettingsInstallNameToolCommand@
 settings-dll-wrap-command = @SettingsDllWrapCommand@
 settings-windres-command = @SettingsWindresCommand@
 settings-libtool-command = @SettingsLibtoolCommand@
diff --git a/hadrian/src/Oracles/Setting.hs b/hadrian/src/Oracles/Setting.hs
index 06ea13d3f8f313b8e0dd2aad1a61dbc7f267dd7b..4331317b68b50f05a0a830725a6b236ae3a8e5e2 100644
--- a/hadrian/src/Oracles/Setting.hs
+++ b/hadrian/src/Oracles/Setting.hs
@@ -114,6 +114,8 @@ data SettingsFileSetting
     | SettingsFileSetting_MergeObjectsFlags
     | SettingsFileSetting_ArCommand
     | SettingsFileSetting_RanlibCommand
+    | SettingsFileSetting_OtoolCommand
+    | SettingsFileSetting_InstallNameToolCommand
     | SettingsFileSetting_DllWrapCommand
     | SettingsFileSetting_WindresCommand
     | SettingsFileSetting_LibtoolCommand
@@ -200,6 +202,8 @@ settingsFileSetting key = lookupValueOrError configFile $ case key of
     SettingsFileSetting_MergeObjectsFlags -> "settings-merge-objects-flags"
     SettingsFileSetting_ArCommand -> "settings-ar-command"
     SettingsFileSetting_RanlibCommand -> "settings-ranlib-command"
+    SettingsFileSetting_OtoolCommand -> "settings-otool-command"
+    SettingsFileSetting_InstallNameToolCommand -> "settings-install_name_tool-command"
     SettingsFileSetting_DllWrapCommand -> "settings-dll-wrap-command"
     SettingsFileSetting_WindresCommand -> "settings-windres-command"
     SettingsFileSetting_LibtoolCommand -> "settings-libtool-command"
diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs
index 430946020c5a53efaa7308553030a97c89d3e30d..f429a8a9d290127cad3705f8dc8d88047633eb0b 100644
--- a/hadrian/src/Rules/Generate.hs
+++ b/hadrian/src/Rules/Generate.hs
@@ -308,6 +308,8 @@ generateSettings = do
         , ("ar flags", expr $ lookupValueOrError configFile "ar-args")
         , ("ar supports at file", expr $ yesNo <$> flag ArSupportsAtFile)
         , ("ranlib command", expr $ settingsFileSetting SettingsFileSetting_RanlibCommand)
+        , ("otool command", expr $ settingsFileSetting SettingsFileSetting_OtoolCommand)
+        , ("install_name_tool command", expr $ settingsFileSetting SettingsFileSetting_InstallNameToolCommand)
         , ("touch command", expr $ settingsFileSetting SettingsFileSetting_TouchCommand)
         , ("dllwrap command", expr $ settingsFileSetting SettingsFileSetting_DllWrapCommand)
         , ("windres command", expr $ settingsFileSetting SettingsFileSetting_WindresCommand)
diff --git a/includes/ghc.mk b/includes/ghc.mk
index f4b85d4e2fba471ae023600f96d14cf5325e28fc..08e865b926d501d1393ee7aa596133c08a6b93e2 100644
--- a/includes/ghc.mk
+++ b/includes/ghc.mk
@@ -233,6 +233,8 @@ $(includes_SETTINGS) : includes/Makefile | $$(dir $$@)/.
 	@echo ',("ar flags", "$(ArArgs)")' >> $@
 	@echo ',("ar supports at file", "$(ArSupportsAtFile)")' >> $@
 	@echo ',("ranlib command", "$(SettingsRanlibCommand)")' >> $@
+	@echo ',("otool command", "$(SettingsOtoolCommand)")' >> $@
+	@echo ',("install_name_tool command", "$(SettingsInstallNameToolCommand)")' >> $@
 	@echo ',("touch command", "$(SettingsTouchCommand)")' >> $@
 	@echo ',("dllwrap command", "$(SettingsDllWrapCommand)")' >> $@
 	@echo ',("windres command", "$(SettingsWindresCommand)")' >> $@
diff --git a/mk/config.mk.in b/mk/config.mk.in
index 11760686eac852fe50acace085f776aed3df48a4..1a9c81fc0a94d6e9c4593cfaa86c00dfe9d9a1a1 100644
--- a/mk/config.mk.in
+++ b/mk/config.mk.in
@@ -504,6 +504,8 @@ SettingsLdFlags = @SettingsLdFlags@
 SettingsMergeObjectsCommand = @SettingsMergeObjectsCommand@
 SettingsMergeObjectsFlags = @SettingsMergeObjectsFlags@
 SettingsArCommand = @SettingsArCommand@
+SettingsOtoolCommand = @SettingsOtoolCommand@
+SettingsInstallNameToolCommand = @SettingsInstallNameToolCommand@
 SettingsRanlibCommand = @SettingsRanlibCommand@
 SettingsDllWrapCommand = @SettingsDllWrapCommand@
 SettingsWindresCommand = @SettingsWindresCommand@
diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T
index 61e525b93847dbe386ca506462672cdfb3527fc5..e469783e802883a8972b5000eeee407d5a45265f 100644
--- a/testsuite/tests/rts/all.T
+++ b/testsuite/tests/rts/all.T
@@ -406,7 +406,7 @@ test('T16514', unless(opsys('mingw32'), skip), compile_and_run, ['T16514_c.cpp -
 test('test-zeroongc', extra_run_opts('-DZ'), compile_and_run, ['-debug'])
 
 test('T13676',
-     [when(opsys('darwin') or opsys('mingw32'), expect_broken(17447)),
+     [when(opsys('mingw32'), expect_broken(17447)),
       extra_files(['T13676.hs'])],
      ghci_script, ['T13676.script'])
 test('InitEventLogging',