[Git][ghc/ghc][master] Linker: replace blind tuple with a datatype + docs

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Aug 14 18:29:56 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -


3 changed files:

- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Linker/Unit.hs


Changes:

=====================================
compiler/GHC/Linker/Dynamic.hs
=====================================
@@ -85,11 +85,11 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
          | OSMinGW32 <- os         = pkgs_with_rts
          | gopt Opt_LinkRts dflags = pkgs_with_rts
          | otherwise               = pkgs_without_rts
-        pkg_link_opts = package_hs_libs ++ extra_libs ++ other_flags
+        pkg_link_opts = hsLibs unit_link_opts ++ extraLibs unit_link_opts ++ otherFlags unit_link_opts
           where
             namever = ghcNameVersion dflags
             ways_   = ways dflags
-            (package_hs_libs, extra_libs, other_flags) = collectLinkOpts namever ways_ pkgs
+            unit_link_opts = collectLinkOpts namever ways_ pkgs
 
         -- probably _stub.o files
         -- and last temporary shared object file


=====================================
compiler/GHC/Linker/Static.hs
=====================================
@@ -156,10 +156,10 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do
         = ([],[])
 
     pkg_link_opts <- do
-        (package_hs_libs, extra_libs, other_flags) <- getUnitLinkOpts namever ways_ unit_env dep_units
-        return $ other_flags ++ dead_strip
-                  ++ pre_hs_libs ++ package_hs_libs ++ post_hs_libs
-                  ++ extra_libs
+        unit_link_opts <- getUnitLinkOpts namever ways_ unit_env dep_units
+        return $ otherFlags unit_link_opts ++ dead_strip
+                  ++ pre_hs_libs ++ hsLibs unit_link_opts ++ post_hs_libs
+                  ++ extraLibs unit_link_opts
                  -- -Wl,-u,<sym> contained in other_flags
                  -- needs to be put before -l<package>,
                  -- otherwise Solaris linker fails linking


=====================================
compiler/GHC/Linker/Unit.hs
=====================================
@@ -1,7 +1,8 @@
 
 -- | Linking Haskell units
 module GHC.Linker.Unit
-   ( collectLinkOpts
+   ( UnitLinkOpts (..)
+   , collectLinkOpts
    , collectArchives
    , getUnitLinkOpts
    , getLibs
@@ -24,20 +25,27 @@ import Control.Monad
 import System.Directory
 import System.FilePath
 
+-- | Linker flags collected from units
+data UnitLinkOpts = UnitLinkOpts
+  { hsLibs     :: [String] -- ^ Haskell libraries (as a list of "-lHSfoo...")
+  , extraLibs  :: [String] -- ^ External libraries (as a list of "-lfoo...")
+  , otherFlags :: [String] -- ^ Extra linker options
+  }
+  deriving (Show)
+
 -- | Find all the link options in these and the preload packages,
 -- returning (package hs lib options, extra library options, other flags)
-getUnitLinkOpts :: GhcNameVersion -> Ways -> UnitEnv -> [UnitId] -> IO ([String], [String], [String])
+getUnitLinkOpts :: GhcNameVersion -> Ways -> UnitEnv -> [UnitId] -> IO UnitLinkOpts
 getUnitLinkOpts namever ways unit_env pkgs = do
     ps <- mayThrowUnitErr $ preloadUnitsInfo' unit_env pkgs
     return (collectLinkOpts namever ways ps)
 
-collectLinkOpts :: GhcNameVersion -> Ways -> [UnitInfo] -> ([String], [String], [String])
-collectLinkOpts namever ways ps =
-    (
-        concatMap (map ("-l" ++) . unitHsLibs namever ways) ps,
-        concatMap (map ("-l" ++) . map ST.unpack . unitExtDepLibsSys) ps,
-        concatMap (map ST.unpack . unitLinkerOptions) ps
-    )
+collectLinkOpts :: GhcNameVersion -> Ways -> [UnitInfo] -> UnitLinkOpts
+collectLinkOpts namever ways ps = UnitLinkOpts
+  { hsLibs     = concatMap (map ("-l" ++) . unitHsLibs namever ways) ps
+  , extraLibs  = concatMap (map ("-l" ++) . map ST.unpack . unitExtDepLibsSys) ps
+  , otherFlags = concatMap (map ST.unpack . unitLinkerOptions) ps
+  }
 
 collectArchives :: GhcNameVersion -> Ways -> UnitInfo -> IO [FilePath]
 collectArchives namever ways pc =



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7602ca23ce2e7786b49c7ef62da8f5f33f767d20

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7602ca23ce2e7786b49c7ef62da8f5f33f767d20
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/20240814/e59dc1a8/attachment-0001.html>


More information about the ghc-commits mailing list