[Git][ghc/ghc][wip/romes/rpath-flag] Introduce -rpath flag for runtime lib search paths

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Thu Dec 21 15:48:42 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/rpath-flag at Glasgow Haskell Compiler / GHC


Commits:
157eee09 by Rodrigo Mesquita at 2023-12-21T11:44:49+00:00
Introduce -rpath flag for runtime lib search paths

Introduces a list flag `-rpath` for users to specify runtime library
search paths where GHC's linker invocations will look for libraries at
load time.

Previously, clients (notably Cabal) would add specify runtime search
paths directly to the linker via @-optl-Wl,-rpath,/actual/path@,
bypassing the compiler abstraction and the special logic GHC has to
handle runtime search paths -- that is especially important on macOS (4ff9329224).

Additionally, this enables a better solution for cabal#7339, for the
above reasons.

Fixes #24272 and enables fixing #19350

- - - - -


5 changed files:

- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs


Changes:

=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -302,6 +302,7 @@ data DynFlags = DynFlags {
 
   includePaths          :: IncludeSpecs,
   libraryPaths          :: [String],
+  libraryRuntimePaths   :: [String],
   frameworkPaths        :: [String],    -- used on darwin only
   cmdlineFrameworks     :: [String],    -- ditto
 
@@ -614,6 +615,7 @@ defaultDynFlags mySettings =
         ldInputs                = [],
         includePaths            = IncludeSpecs [] [] [],
         libraryPaths            = [],
+        libraryRuntimePaths     = [],
         frameworkPaths          = [],
         cmdlineFrameworks       = [],
         rtsOpts                 = Nothing,


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -214,6 +214,7 @@ module GHC.Driver.Session (
         LinkerInfo(..),
         CompilerInfo(..),
         useXLinkerRPath,
+        optXLinkerRPath,
 
         -- * Include specifications
         IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes,
@@ -1160,6 +1161,7 @@ dynamic_flags_deps = [
         ------- Libraries ---------------------------------------------------
   , make_ord_flag defFlag "L"   (Prefix addLibraryPath)
   , make_ord_flag defFlag "l"   (hasArg (addLdInputs . Option . ("-l" ++)))
+  , make_ord_flag defFlag "rpath" (HasArg addLibraryRuntimePath)
 
         ------- Frameworks --------------------------------------------------
         -- -framework-path should really be -F ...
@@ -3372,7 +3374,7 @@ parseEnvFile envfile = mapM_ parseEntry . lines
 -----------------------------------------------------------------------------
 -- Paths & Libraries
 
-addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
+addImportPath, addLibraryPath, addIncludePath, addLibraryRuntimePath, addFrameworkPath :: FilePath -> DynP ()
 
 -- -i on its own deletes the import paths
 addImportPath "" = upd (\s -> s{importPaths = []})
@@ -3385,6 +3387,9 @@ addIncludePath p =
   upd (\s -> s{includePaths =
                   addGlobalInclude (includePaths s) (splitPathList p)})
 
+addLibraryRuntimePath p =
+  upd (\s -> s{libraryRuntimePaths = libraryRuntimePaths s ++ splitPathList p})
+
 addFrameworkPath p =
   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
 


=====================================
compiler/GHC/Linker/Dynamic.hs
=====================================
@@ -52,7 +52,7 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
     pkgs_with_rts <- mayThrowUnitErr (preloadUnitsInfo' unit_env dep_packages)
 
     let pkg_lib_paths = collectLibraryDirs (ways dflags) pkgs_with_rts
-    let pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
+        pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
         get_pkg_lib_path_opts l
          | osElfTarget os || osMachOTarget os
          , dynLibLoader dflags == SystemDependent
@@ -64,7 +64,9 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
          | otherwise = ["-L" ++ l]
 
     let lib_paths = libraryPaths dflags
-    let lib_path_opts = map ("-L"++) lib_paths
+        lib_path_opts = map ("-L"++) lib_paths
+        r_paths = libraryRuntimePaths dflags
+        r_path_opts = concatMap optXLinkerRPath r_paths
 
     -- In general we don't want to link our dynamic libs against the RTS
     -- package, because the RTS lib comes in several flavours and we want to be
@@ -127,6 +129,7 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
                  ++ extra_ld_inputs
                  ++ map Option (
                     lib_path_opts
+                 ++ r_path_opts
                  ++ pkg_lib_path_opts
                  ++ pkg_link_opts
                 ))
@@ -190,6 +193,7 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
                      else [ Option "-Wl,-read_only_relocs,suppress" ])
                  ++ [ Option "-install_name", Option instName ]
                  ++ map Option lib_path_opts
+                 ++ map Option r_path_opts
                  ++ extra_ld_inputs
                  ++ map Option framework_opts
                  ++ map Option pkg_lib_path_opts
@@ -205,7 +209,7 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
               )
             -- Make sure to honour -fno-use-rpaths if set on darwin as well; see #20004
             when (gopt Opt_RPath dflags) $
-              runInjectRPaths logger (toolSettings dflags) pkg_lib_paths output_fn
+              runInjectRPaths logger (toolSettings dflags) (pkg_lib_paths ++ r_paths) output_fn
         _ -> do
             -------------------------------------------------------------------
             -- Making a DSO
@@ -234,6 +238,7 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
                  ++ [ Option ("-Wl,-h," ++ takeFileName output_fn) ]
                  ++ extra_ld_inputs
                  ++ map Option lib_path_opts
+                 ++ map Option r_path_opts
                  ++ map Option pkg_lib_path_opts
                  ++ map Option pkg_link_opts
               )


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -340,7 +340,8 @@ loadCmdLineLibs'' interp hsc_env pls =
   do
 
       let dflags@(DynFlags { ldInputs = cmdline_ld_inputs
-                           , libraryPaths = lib_paths_base})
+                           , libraryPaths = lib_paths_base
+                           , libraryRuntimePaths = r_paths_base })
             = hsc_dflags hsc_env
       let logger = hsc_logger hsc_env
 
@@ -393,9 +394,13 @@ loadCmdLineLibs'' interp hsc_env pls =
            let all_paths = let paths = takeDirectory (pgm_c dflags)
                                      : framework_paths
                                     ++ lib_paths_base
+                                    ++ r_paths_base
+                                    -- OMES:TODO: Should this also have gcc_paths?
+                                    -- in that case, we should just add
+                                    -- lib_paths
                                     ++ [ takeDirectory dll | DLLPath dll <- libspecs ]
                            in nubOrd $ map normalise paths
-           let lib_paths = nubOrd $ lib_paths_base ++ gcc_paths
+           let lib_paths = nubOrd $ lib_paths_base ++ r_paths_base ++ gcc_paths
            all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
            pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
 


=====================================
compiler/GHC/Linker/Static.hs
=====================================
@@ -121,11 +121,13 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do
     let
       dead_strip
         | gopt Opt_WholeArchiveHsLibs dflags = []
-        | otherwise = if osSubsectionsViaSymbols (platformOS platform)
-                        then ["-Wl,-dead_strip"]
-                        else []
-    let lib_paths = libraryPaths dflags
-    let lib_path_opts = map ("-L"++) lib_paths
+        | osSubsectionsViaSymbols (platformOS platform) = ["-Wl,-dead_strip"]
+        | otherwise = []
+      lib_paths = libraryPaths dflags
+      lib_path_opts = map ("-L"++) lib_paths
+      r_paths = libraryRuntimePaths dflags
+      r_path_opts = concatMap optXLinkerRPath r_paths
+
 
     extraLinkObj <- maybeToList <$> mkExtraObjToLinkIntoBinary logger tmpfs dflags unit_state
     noteLinkObjs <- mkNoteObjsToLinkIntoBinary logger tmpfs dflags unit_env dep_units
@@ -172,7 +174,7 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do
           runLink logger tmpfs linker_config args
           -- Make sure to honour -fno-use-rpaths if set on darwin as well; see #20004
           when (platformOS platform == OSDarwin && gopt Opt_RPath dflags) $
-            GHC.Linker.MacOS.runInjectRPaths logger (toolSettings dflags) pkg_lib_paths output_fn
+            GHC.Linker.MacOS.runInjectRPaths logger (toolSettings dflags) (pkg_lib_paths ++ r_paths) output_fn
 
     link dflags (
                        map GHC.SysTools.Option verbFlags
@@ -230,7 +232,8 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do
                           else [])
 
                       ++ o_files
-                      ++ lib_path_opts)
+                      ++ lib_path_opts
+                      ++ r_path_opts)
                       ++ extra_ld_inputs
                       ++ map GHC.SysTools.Option (
                          rc_objs



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/157eee09b23577798db23bdf2ad4c19f3ba29d99

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/157eee09b23577798db23bdf2ad4c19f3ba29d99
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/20231221/03e4f82c/attachment-0001.html>


More information about the ghc-commits mailing list