[commit: ghc] master: add Solaris' linker warning messages filtering into link phase (524f15d)

git at git.haskell.org git at git.haskell.org
Mon Jul 28 14:37:31 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/524f15de1262d387ccd8075b68ed310ce5305068/ghc

>---------------------------------------------------------------

commit 524f15de1262d387ccd8075b68ed310ce5305068
Author: Karel Gardas <karel.gardas at centrum.cz>
Date:   Mon Jul 28 07:49:40 2014 -0500

    add Solaris' linker warning messages filtering into link phase
    
    Summary:
    Solaris ld emits harmless warning messages about unresolved
    symbol in case of compiling into shared library when we do not
    link against all the required libs. That is the case of GHC which
    does not link against RTS library explicitly in order to be able to
    chose the library later based on binary application linking
    parameters. The warnings look like:
    
    Undefined                       first referenced
     symbol                             in file
    stg_ap_n_fast                       ./T2386_Lib.o
    stg_upd_frame_info                  ./T2386_Lib.o
    templatezmhaskell_LanguageziHaskellziTHziLib_litE_closure ./T2386_Lib.o
    templatezmhaskell_LanguageziHaskellziTHziLib_appE_closure ./T2386_Lib.o
    templatezmhaskell_LanguageziHaskellziTHziLib_conE_closure ./T2386_Lib.o
    templatezmhaskell_LanguageziHaskellziTHziSyntax_mkNameGzud_closure ./T2386_Lib.o
    newCAF                              ./T2386_Lib.o
    stg_bh_upd_frame_info               ./T2386_Lib.o
    stg_ap_ppp_fast                     ./T2386_Lib.o
    templatezmhaskell_LanguageziHaskellziTHziLib_stringL_closure ./T2386_Lib.o
    stg_ap_p_fast                       ./T2386_Lib.o
    stg_ap_pp_fast                      ./T2386_Lib.o
    ld: warning: symbol referencing errors
    
    this is actually coming from T2386 testcase. The emitting of those
    warnings is also a reason why so many TH testcases fail on Solaris.
    
    The patch provides filter which filters out only linker warnings.
    
    Test Plan: validate
    
    Reviewers: austin
    
    Reviewed By: austin
    
    Subscribers: phaskell, simonmar, relrod, carter
    
    Differential Revision: https://phabricator.haskell.org/D94


>---------------------------------------------------------------

524f15de1262d387ccd8075b68ed310ce5305068
 compiler/main/SysTools.lhs | 52 +++++++++++++++++++++++++++++++++++++++++++++-
 1 file changed, 51 insertions(+), 1 deletion(-)

diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs
index 3b25c91..adb8d31 100644
--- a/compiler/main/SysTools.lhs
+++ b/compiler/main/SysTools.lhs
@@ -825,7 +825,57 @@ runLink dflags args = do
       args1     = map Option (getOpts dflags opt_l)
       args2     = args0 ++ args1 ++ args ++ linkargs
   mb_env <- getGccEnv args2
-  runSomethingFiltered dflags id "Linker" p args2 mb_env
+  runSomethingFiltered dflags ld_filter "Linker" p args2 mb_env
+  where
+    ld_filter = case (platformOS (targetPlatform dflags)) of
+                  OSSolaris2 -> sunos_ld_filter
+                  _ -> id
+{-
+  SunOS/Solaris ld emits harmless warning messages about unresolved
+  symbol in case of compiling into shared library when we do not
+  link against all the required libs. That is the case of GHC which
+  does not link against RTS library explicitly in order to be able to
+  chose the library later based on binary application linking
+  parameters. The warnings look like:
+
+Undefined                       first referenced
+ symbol                             in file
+stg_ap_n_fast                       ./T2386_Lib.o
+stg_upd_frame_info                  ./T2386_Lib.o
+templatezmhaskell_LanguageziHaskellziTHziLib_litE_closure ./T2386_Lib.o
+templatezmhaskell_LanguageziHaskellziTHziLib_appE_closure ./T2386_Lib.o
+templatezmhaskell_LanguageziHaskellziTHziLib_conE_closure ./T2386_Lib.o
+templatezmhaskell_LanguageziHaskellziTHziSyntax_mkNameGzud_closure ./T2386_Lib.o
+newCAF                              ./T2386_Lib.o
+stg_bh_upd_frame_info               ./T2386_Lib.o
+stg_ap_ppp_fast                     ./T2386_Lib.o
+templatezmhaskell_LanguageziHaskellziTHziLib_stringL_closure ./T2386_Lib.o
+stg_ap_p_fast                       ./T2386_Lib.o
+stg_ap_pp_fast                      ./T2386_Lib.o
+ld: warning: symbol referencing errors
+
+  this is actually coming from T2386 testcase. The emitting of those
+  warnings is also a reason why so many TH testcases fail on Solaris.
+
+  Following filter code is SunOS/Solaris linker specific and should
+  filter out only linker warnings. Please note that the logic is a
+  little bit more complex due to simple reason that we need to preserve
+  any other linker emitted messages. If there are any. Simply speaking
+  if we see "Undefined" and later "ld: warning:..." then we omit all
+  text between (including) the marks. Otherwise we copy whole output.
+-}
+    sunos_ld_filter :: String -> String
+    sunos_ld_filter = unlines . sunos_ld_filter' . lines
+    sunos_ld_filter' x = if (undefined_found x && ld_warning_found x)
+                         then (ld_prefix x) ++ (ld_postfix x)
+                         else x
+    breakStartsWith x y = break (isPrefixOf x) y
+    ld_prefix = fst . breakStartsWith "Undefined"
+    undefined_found = not . null . snd . breakStartsWith "Undefined"
+    ld_warn_break = breakStartsWith "ld: warning: symbol referencing errors"
+    ld_postfix = tail . snd . ld_warn_break
+    ld_warning_found = not . null . snd . ld_warn_break
+
 
 runLibtool :: DynFlags -> [Option] -> IO ()
 runLibtool dflags args = do



More information about the ghc-commits mailing list