[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: [macOS] improved runpath handling

Marge Bot gitlab at gitlab.haskell.org
Tue Sep 8 02:51:09 UTC 2020



 Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00
[macOS] improved runpath handling

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)

- - - - -
df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00
Move DynFlags test into updateModDetailsIdInfos's caller (#17957)

- - - - -
9c23e2d6 by Daishi Nakajima at 2020-09-07T22:51:01-04:00
testsuite: Output performance test results in tabular format
this was suggested in #18417.

Change the print format of the values.
* Shorten commit hash
* Reduce precision of the "Value" field
* Shorten metrics name
  * e.g. runtime/bytes allocated -> run/alloc
* Shorten "MetricsChange"
  * e.g. unchanged -> unch, increased -> incr

And, print the baseline environment if there are baselines that were
measured in a different environment than the current environment.

If all "Baseline commit" are the same, print it once.

- - - - -
c86e667a by Ben Gamari at 2020-09-07T22:51:01-04:00
gitlab-ci: Handle distributions without locales

Previously we would assume that the `locale` utility exists. However,
this is not so on Alpine as musl's locale support is essentially
non-existent.

(cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e)

- - - - -
86120f70 by Ben Gamari at 2020-09-07T22:51:01-04:00
gitlab-ci: Accept Centos 7 C.utf8 locale

Centos apparently has C.utf8 rather than C.UTF-8.

(cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464)

- - - - -


21 changed files:

- .gitlab/ci.sh
- aclocal.m4
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/UpdateIdInfos.hs
- compiler/GHC/Runtime/Linker.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/SysTools.hs
- compiler/GHC/SysTools/Tasks.hs
- configure.ac
- docs/users_guide/phases.rst
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- includes/ghc.mk
- mk/config.mk.in
- testsuite/driver/perf_notes.py
- testsuite/driver/runtests.py
- testsuite/driver/testutil.py
- testsuite/tests/rts/all.T


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -58,6 +58,12 @@ function run() {
 TOP="$(pwd)"
 
 function setup_locale() {
+  # Musl doesn't provide locale support at all...
+  if ! which locale > /dev/null; then
+    info "No locale executable. Skipping locale setup..."
+    return
+  fi
+
   # BSD grep terminates early with -q, consequently locale -a will get a
   # SIGPIPE and the pipeline will fail with pipefail.
   shopt -o -u pipefail
@@ -70,6 +76,9 @@ function setup_locale() {
   elif locale -a | grep -q en_US.UTF-8; then
     # Centos doesn't have C.UTF-8
     export LANG=en_US.UTF-8
+  elif locale -a | grep -q en_US.utf8; then
+    # Centos doesn't have C.UTF-8
+    export LANG=en_US.utf8
   else
     error "Failed to find usable locale"
     info "Available locales:"


=====================================
aclocal.m4
=====================================
@@ -602,6 +602,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"
@@ -621,6 +633,8 @@ AC_DEFUN([FP_SETTINGS],
     AC_SUBST(SettingsMergeObjectsFlags)
     AC_SUBST(SettingsArCommand)
     AC_SUBST(SettingsRanlibCommand)
+    AC_SUBST(SettingsOtoolCommand)
+    AC_SUBST(SettingsInstallNameToolCommand)
     AC_SUBST(SettingsDllWrapCommand)
     AC_SUBST(SettingsWindresCommand)
     AC_SUBST(SettingsLibtoolCommand)


=====================================
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?
@@ -1188,8 +1237,11 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do
                       hscGenHardCode hsc_env' cgguts mod_location output_fn
 
                     final_iface <- liftIO (mkFullIface hsc_env'{hsc_dflags=iface_dflags} partial_iface (Just cg_infos))
-                    let final_mod_details = {-# SCC updateModDetailsIdInfos #-}
-                                            updateModDetailsIdInfos iface_dflags cg_infos mod_details
+                    let final_mod_details
+                           | gopt Opt_OmitInterfacePragmas iface_dflags
+                           = mod_details
+                           | otherwise = {-# SCC updateModDetailsIdInfos #-}
+                                         updateModDetailsIdInfos cg_infos mod_details
                     setIface final_iface final_mod_details
 
                     -- See Note [Writing interface files]
@@ -1787,9 +1839,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 +1911,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 [])
                     ))
 


=====================================
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)]


=====================================
compiler/GHC/Iface/UpdateIdInfos.hs
=====================================
@@ -8,7 +8,6 @@ import GHC.Prelude
 
 import GHC.Core
 import GHC.Core.InstEnv
-import GHC.Driver.Session
 import GHC.Driver.Types
 import GHC.StgToCmm.Types (CgInfos (..))
 import GHC.Types.Id
@@ -28,16 +27,11 @@ import GHC.Utils.Panic
 -- See Note [Conveying CAF-info and LFInfo between modules] in
 -- GHC.StgToCmm.Types.
 updateModDetailsIdInfos
-  :: DynFlags
-  -> CgInfos
+  :: CgInfos
   -> ModDetails -- ^ ModDetails to update
   -> ModDetails
 
-updateModDetailsIdInfos dflags _ mod_details
-  | gopt Opt_OmitInterfacePragmas dflags
-  = mod_details
-
-updateModDetailsIdInfos _ cg_infos mod_details =
+updateModDetailsIdInfos cg_infos mod_details =
   let
     ModDetails{ md_types = type_env -- for unfoldings
               , md_insts = insts


=====================================
compiler/GHC/Runtime/Linker.hs
=====================================
@@ -929,20 +929,22 @@ dynLoadObjs hsc_env pls at 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,


=====================================
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])


=====================================
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,[])


=====================================
compiler/GHC/SysTools.hs
=====================================
@@ -261,7 +261,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]
@@ -386,8 +389,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


=====================================
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 at .
+--
+-- 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


=====================================
configure.ac
=====================================
@@ -699,6 +699,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
@@ -1522,6 +1534,8 @@ echo "\
    libtool      : $LibtoolCmd
    objdump      : $ObjdumpCmd
    ranlib       : $RanlibCmd
+   otool        : $OtoolCmd
+   install_name_tool : $InstallNameToolCmd
    windres      : $WindresCmd
    dllwrap      : $DllWrapCmd
    genlib       : $GenlibCmd


=====================================
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


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -152,6 +152,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@


=====================================
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"


=====================================
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)


=====================================
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)")' >> $@


=====================================
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@


=====================================
testsuite/driver/perf_notes.py
=====================================
@@ -22,7 +22,7 @@ import sys
 from collections import namedtuple
 from math import ceil, trunc
 
-from testutil import passed, failBecause, testing_metrics
+from testutil import passed, failBecause, testing_metrics, print_table
 from term_color import Color, colored
 
 from my_typing import *
@@ -45,6 +45,14 @@ def inside_git_repo() -> bool:
 def is_worktree_dirty() -> bool:
     return subprocess.check_output(['git', 'status', '--porcelain']) != b''
 
+# Get length of abbreviated git commit hash
+def get_abbrev_hash_length() -> int:
+    try:
+        return len(subprocess.check_output(['git', 'rev-parse',
+                                            '--short', 'HEAD']).strip())
+    except subprocess.CalledProcessError:
+        return 10
+
 #
 # Some data access functions. At the moment this uses git notes.
 #
@@ -100,6 +108,15 @@ class MetricChange(Enum):
         }
         return strings[self]
 
+    def short_name(self):
+        strings = {
+            MetricChange.NewMetric: "new",
+            MetricChange.NoChange:  "unch",
+            MetricChange.Increase:  "incr",
+            MetricChange.Decrease:  "decr"
+        }
+        return strings[self]
+
 AllowedPerfChange = NamedTuple('AllowedPerfChange',
                                [('direction', MetricChange),
                                 ('metrics', List[str]),
@@ -758,7 +775,7 @@ def main() -> None:
         exit(0)
 
     #
-    # String utilities for pretty-printing
+    # Print the data in tablular format
     #
 
     #                  T1234                 T1234
@@ -770,11 +787,12 @@ def main() -> None:
     # HEAD~1           10023                 10023
     # HEAD~2           21234                 21234
     # HEAD~3           20000                 20000
-
-    # Data is already in colum major format, so do that, calculate column widths
-    # then transpose and print each row.
     def strMetric(x):
         return '{:.2f}'.format(x.value) if x != None else ""
+    # Data is in colum major format, so transpose and pass to print_table.
+    T = TypeVar('T')
+    def transpose(xss: List[List[T]]) -> List[List[T]]:
+        return list(map(list, zip(*xss)))
 
     headerCols = [ ["","","","Commit"] ] \
                 + [ [name, metric, way, env] for (env, name, metric, way) in testSeries ]
@@ -782,17 +800,7 @@ def main() -> None:
                 + [ [strMetric(get_commit_metric(ref, commit, env, name, metric, way)) \
                         for commit in commits ] \
                         for (env, name, metric, way) in testSeries ]
-    colWidths = [max([2+len(cell) for cell in colH + colD]) for (colH,colD) in zip(headerCols, dataCols)]
-    col_fmts = ['{:>' + str(w) + '}' for w in colWidths]
-
-    def printCols(cols):
-        for row in zip(*cols):
-            # print(list(zip(col_fmts, row)))
-            print(''.join([f.format(cell) for (f,cell) in zip(col_fmts, row)]))
-
-    printCols(headerCols)
-    print('-'*(sum(colWidths)+2))
-    printCols(dataCols)
+    print_table(transpose(headerCols), transpose(dataCols))
 
 if __name__ == '__main__':
     main()


=====================================
testsuite/driver/runtests.py
=====================================
@@ -23,11 +23,11 @@ import traceback
 # So we import it here first, so that the testsuite doesn't appear to fail.
 import subprocess
 
-from testutil import getStdout, Watcher, str_warn, str_info
+from testutil import getStdout, Watcher, str_warn, str_info, print_table, shorten_metric_name
 from testglobals import getConfig, ghc_env, getTestRun, TestConfig, \
                         TestOptions, brokens, PerfMetric
 from my_typing import TestName
-from perf_notes import MetricChange, GitRef, inside_git_repo, is_worktree_dirty, format_perf_stat
+from perf_notes import MetricChange, GitRef, inside_git_repo, is_worktree_dirty, format_perf_stat, get_abbrev_hash_length, is_commit_hash
 from junit import junit
 import term_color
 from term_color import Color, colored
@@ -341,23 +341,52 @@ def cleanup_and_exit(exitcode):
     exit(exitcode)
 
 def tabulate_metrics(metrics: List[PerfMetric]) -> None:
-    for metric in sorted(metrics, key=lambda m: (m.stat.test, m.stat.way, m.stat.metric)):
-        print("{test:24}  {metric:40}  {value:15.3f}".format(
-            test = "{}({})".format(metric.stat.test, metric.stat.way),
-            metric = metric.stat.metric,
-            value = metric.stat.value
-        ))
-        if metric.baseline is not None:
-            val0 = metric.baseline.perfStat.value
-            val1 = metric.stat.value
-            rel = 100 * (val1 - val0) / val0
-            print("{space:24}  {herald:40}  {value:15.3f}  [{direction}, {rel:2.1f}%]".format(
-                space = "",
-                herald = "(baseline @ {commit})".format(
-                    commit = metric.baseline.commit),
-                value = val0,
-                direction = metric.change,
-                rel = rel
+    abbrevLen = get_abbrev_hash_length()
+    hasBaseline = any([x.baseline is not None for x in metrics])
+    baselineCommitSet = set([x.baseline.commit for x in metrics if x.baseline is not None])
+    hideBaselineCommit = not hasBaseline or len(baselineCommitSet) == 1
+    hideBaselineEnv = not hasBaseline or all(
+        [x.stat.test_env == x.baseline.perfStat.test_env
+         for x in metrics if x.baseline is not None])
+    def row(cells: Tuple[str, str, str, str, str, str, str]) -> List[str]:
+        return [x for (idx, x) in enumerate(list(cells)) if
+                (idx != 2 or not hideBaselineCommit) and
+                (idx != 3 or not hideBaselineEnv )]
+
+    headerRows = [
+        row(("", "", "Baseline", "Baseline", "Baseline", "", "")),
+        row(("Test", "Metric", "commit", "environment", "value", "New value", "Change"))
+    ]
+    def strDiff(x: PerfMetric) -> str:
+        if x.baseline is None:
+            return ""
+        val0 = x.baseline.perfStat.value
+        val1 = x.stat.value
+        return "{}({:+2.1f}%)".format(x.change.short_name(), 100 * (val1 - val0) / val0)
+    dataRows = [row((
+        "{}({})".format(x.stat.test, x.stat.way),
+        shorten_metric_name(x.stat.metric),
+          "{}".format(x.baseline.commit[:abbrevLen]
+                      if is_commit_hash(x.baseline.commit) else x.baseline.commit)
+          if x.baseline is not None else "",
+        "{}".format(x.baseline.perfStat.test_env)
+          if x.baseline is not None else "",
+        "{:13.1f}".format(x.baseline.perfStat.value)
+          if x.baseline is not None else "",
+        "{:13.1f}".format(x.stat.value),
+        strDiff(x)
+    )) for x in sorted(metrics, key =
+                      lambda m: (m.stat.test, m.stat.way, m.stat.metric))]
+    print_table(headerRows, dataRows, 1)
+    print("")
+    if hasBaseline:
+        if hideBaselineEnv:
+            print("* All baselines were measured in the same environment as this test run")
+        if hideBaselineCommit:
+            commit = next(iter(baselineCommitSet))
+            print("* All baseline commits are {}".format(
+                commit[:abbrevLen]
+                if is_commit_hash(commit) else commit
             ))
 
 # First collect all the tests to be run


=====================================
testsuite/driver/testutil.py
=====================================
@@ -144,3 +144,29 @@ def memoize(f):
 
     cached._cache = None
     return cached
+
+# Print the matrix data in a tabular format.
+def print_table(header_rows: List[List[str]], data_rows: List[List[str]], padding=2) -> None:
+    # Calculate column widths then print each row.
+    colWidths = [(0 if idx == 0 else padding) + max([len(cell) for cell in col])
+                 for (idx, col) in enumerate(zip(*(header_rows + data_rows)))]
+    col_fmts = ['{:>' + str(w) + '}' for w in colWidths]
+
+    def printCols(cols):
+        for row in cols:
+            print(''.join([f.format(cell) for (f,cell) in zip(col_fmts, row)]))
+
+    printCols(header_rows)
+    print('-' * sum(colWidths))
+    printCols(data_rows)
+
+def shorten_metric_name(name: str) -> str:
+    dic = {
+        "runtime/bytes allocated": "run/alloc",
+        "runtime/peak_megabytes_allocated": "run/peak",
+        "runtime/max_bytes_used": "run/max",
+        "compile_time/bytes allocated": "ghc/alloc",
+        "compile_time/peak_megabytes_allocated": "ghc/peak",
+        "compile_time/max_bytes_used": "ghc/max",
+    }
+    return dic.get(name, name)


=====================================
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',



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80f3f4a6922c2854af941853482998fe27b163db...86120f70895932b4a8996ac24e32b1cbd6564e8e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80f3f4a6922c2854af941853482998fe27b163db...86120f70895932b4a8996ac24e32b1cbd6564e8e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200907/a5b768b8/attachment-0001.html>


More information about the ghc-commits mailing list