never executed always true always false
    1 {-# LANGUAGE ScopedTypeVariables #-}
    2 -----------------------------------------------------------------------------
    3 --
    4 -- Compiler information functions
    5 --
    6 -- (c) The GHC Team 2017
    7 --
    8 -----------------------------------------------------------------------------
    9 module GHC.SysTools.Info where
   10 
   11 import GHC.Utils.Exception
   12 import GHC.Utils.Error
   13 import GHC.Driver.Session
   14 import GHC.Utils.Outputable
   15 import GHC.Utils.Misc
   16 import GHC.Utils.Logger
   17 
   18 import Data.List ( isInfixOf, isPrefixOf )
   19 import Data.IORef
   20 
   21 import System.IO
   22 
   23 import GHC.Platform
   24 import GHC.Prelude
   25 
   26 import GHC.SysTools.Process
   27 
   28 {- Note [Run-time linker info]
   29 
   30 See also: #5240, #6063, #10110
   31 
   32 Before 'runLink', we need to be sure to get the relevant information
   33 about the linker we're using at runtime to see if we need any extra
   34 options. For example, GNU ld requires '--reduce-memory-overheads' and
   35 '--hash-size=31' in order to use reasonable amounts of memory (see
   36 trac #5240.) But this isn't supported in GNU gold.
   37 
   38 Generally, the linker changing from what was detected at ./configure
   39 time has always been possible using -pgml, but on Linux it can happen
   40 'transparently' by installing packages like binutils-gold, which
   41 change what /usr/bin/ld actually points to.
   42 
   43 Clang vs GCC notes:
   44 
   45 For gcc, 'gcc -Wl,--version' gives a bunch of output about how to
   46 invoke the linker before the version information string. For 'clang',
   47 the version information for 'ld' is all that's output. For this
   48 reason, we typically need to slurp up all of the standard error output
   49 and look through it.
   50 
   51 Other notes:
   52 
   53 We cache the LinkerInfo inside DynFlags, since clients may link
   54 multiple times. The definition of LinkerInfo is there to avoid a
   55 circular dependency.
   56 
   57 -}
   58 
   59 {- Note [ELF needed shared libs]
   60 
   61 Some distributions change the link editor's default handling of
   62 ELF DT_NEEDED tags to include only those shared objects that are
   63 needed to resolve undefined symbols. For Template Haskell we need
   64 the last temporary shared library also if it is not needed for the
   65 currently linked temporary shared library. We specify --no-as-needed
   66 to override the default. This flag exists in GNU ld and GNU gold.
   67 
   68 The flag is only needed on ELF systems. On Windows (PE) and Mac OS X
   69 (Mach-O) the flag is not needed.
   70 
   71 -}
   72 
   73 {- Note [Windows static libGCC]
   74 
   75 The GCC versions being upgraded to in #10726 are configured with
   76 dynamic linking of libgcc supported. This results in libgcc being
   77 linked dynamically when a shared library is created.
   78 
   79 This introduces thus an extra dependency on GCC dll that was not
   80 needed before by shared libraries created with GHC. This is a particular
   81 issue on Windows because you get a non-obvious error due to this missing
   82 dependency. This dependent dll is also not commonly on your path.
   83 
   84 For this reason using the static libgcc is preferred as it preserves
   85 the same behaviour that existed before. There are however some very good
   86 reasons to have the shared version as well as described on page 181 of
   87 https://gcc.gnu.org/onlinedocs/gcc-5.2.0/gcc.pdf :
   88 
   89 "There are several situations in which an application should use the
   90  shared ‘libgcc’ instead of the static version. The most common of these
   91  is when the application wishes to throw and catch exceptions across different
   92  shared libraries. In that case, each of the libraries as well as the application
   93  itself should use the shared ‘libgcc’. "
   94 
   95 -}
   96 
   97 neededLinkArgs :: LinkerInfo -> [Option]
   98 neededLinkArgs (GnuLD o)     = o
   99 neededLinkArgs (GnuGold o)   = o
  100 neededLinkArgs (LlvmLLD o)   = o
  101 neededLinkArgs (DarwinLD o)  = o
  102 neededLinkArgs (SolarisLD o) = o
  103 neededLinkArgs (AixLD o)     = o
  104 neededLinkArgs UnknownLD     = []
  105 
  106 -- Grab linker info and cache it in DynFlags.
  107 getLinkerInfo :: Logger -> DynFlags -> IO LinkerInfo
  108 getLinkerInfo logger dflags = do
  109   info <- readIORef (rtldInfo dflags)
  110   case info of
  111     Just v  -> return v
  112     Nothing -> do
  113       v <- getLinkerInfo' logger dflags
  114       writeIORef (rtldInfo dflags) (Just v)
  115       return v
  116 
  117 -- See Note [Run-time linker info].
  118 getLinkerInfo' :: Logger -> DynFlags -> IO LinkerInfo
  119 getLinkerInfo' logger dflags = do
  120   let platform = targetPlatform dflags
  121       os = platformOS platform
  122       (pgm,args0) = pgm_l dflags
  123       args1       = map Option (getOpts dflags opt_l)
  124       args2       = args0 ++ args1
  125       args3       = filter notNull (map showOpt args2)
  126 
  127       -- Try to grab the info from the process output.
  128       parseLinkerInfo stdo _stde _exitc
  129         | any ("GNU ld" `isPrefixOf`) stdo =
  130           -- GNU ld specifically needs to use less memory. This especially
  131           -- hurts on small object files. #5240.
  132           -- Set DT_NEEDED for all shared libraries. #10110.
  133           -- TODO: Investigate if these help or hurt when using split sections.
  134           return (GnuLD $ map Option ["-Wl,--hash-size=31",
  135                                       "-Wl,--reduce-memory-overheads",
  136                                       -- ELF specific flag
  137                                       -- see Note [ELF needed shared libs]
  138                                       "-Wl,--no-as-needed"])
  139 
  140         | any ("GNU gold" `isPrefixOf`) stdo =
  141           -- GNU gold only needs --no-as-needed. #10110.
  142           -- ELF specific flag, see Note [ELF needed shared libs]
  143           return (GnuGold [Option "-Wl,--no-as-needed"])
  144 
  145         | any ("LLD" `isPrefixOf`) stdo =
  146           return (LlvmLLD $ map Option [ --see Note [ELF needed shared libs]
  147                                         "-Wl,--no-as-needed"])
  148 
  149          -- Unknown linker.
  150         | otherwise = fail "invalid --version output, or linker is unsupported"
  151 
  152   -- Process the executable call
  153   catchIO (
  154     case os of
  155       OSSolaris2 ->
  156         -- Solaris uses its own Solaris linker. Even all
  157         -- GNU C are recommended to configure with Solaris
  158         -- linker instead of using GNU binutils linker. Also
  159         -- all GCC distributed with Solaris follows this rule
  160         -- precisely so we assume here, the Solaris linker is
  161         -- used.
  162         return $ SolarisLD []
  163       OSAIX ->
  164         -- IBM AIX uses its own non-binutils linker as well
  165         return $ AixLD []
  166       OSDarwin ->
  167         -- Darwin has neither GNU Gold or GNU LD, but a strange linker
  168         -- that doesn't support --version. We can just assume that's
  169         -- what we're using.
  170         return $ DarwinLD []
  171       OSMinGW32 ->
  172         -- GHC doesn't support anything but GNU ld on Windows anyway.
  173         -- Process creation is also fairly expensive on win32, so
  174         -- we short-circuit here.
  175         return $ GnuLD $ map Option
  176           [ -- Reduce ld memory usage
  177             "-Wl,--hash-size=31"
  178           , "-Wl,--reduce-memory-overheads"
  179             -- Emit gcc stack checks
  180             -- Note [Windows stack usage]
  181           , "-fstack-check"
  182             -- Force static linking of libGCC
  183             -- Note [Windows static libGCC]
  184           , "-static-libgcc" ]
  185       _ -> do
  186         -- In practice, we use the compiler as the linker here. Pass
  187         -- -Wl,--version to get linker version info.
  188         (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm
  189                                (["-Wl,--version"] ++ args3)
  190                                c_locale_env
  191         -- Split the output by lines to make certain kinds
  192         -- of processing easier. In particular, 'clang' and 'gcc'
  193         -- have slightly different outputs for '-Wl,--version', but
  194         -- it's still easy to figure out.
  195         parseLinkerInfo (lines stdo) (lines stde) exitc
  196     )
  197     (\err -> do
  198         debugTraceMsg logger 2
  199             (text "Error (figuring out linker information):" <+>
  200              text (show err))
  201         errorMsg logger $ hang (text "Warning:") 9 $
  202           text "Couldn't figure out linker information!" $$
  203           text "Make sure you're using GNU ld, GNU gold" <+>
  204           text "or the built in OS X linker, etc."
  205         return UnknownLD
  206     )
  207 
  208 -- | Grab compiler info and cache it in DynFlags.
  209 getCompilerInfo :: Logger -> DynFlags -> IO CompilerInfo
  210 getCompilerInfo logger dflags = do
  211   info <- readIORef (rtccInfo dflags)
  212   case info of
  213     Just v  -> return v
  214     Nothing -> do
  215       let pgm = pgm_c dflags
  216       v <- getCompilerInfo' logger pgm
  217       writeIORef (rtccInfo dflags) (Just v)
  218       return v
  219 
  220 -- | Grab assembler info and cache it in DynFlags.
  221 getAssemblerInfo :: Logger -> DynFlags -> IO CompilerInfo
  222 getAssemblerInfo logger dflags = do
  223   info <- readIORef (rtasmInfo dflags)
  224   case info of
  225     Just v  -> return v
  226     Nothing -> do
  227       let (pgm, _) = pgm_a dflags
  228       v <- getCompilerInfo' logger pgm
  229       writeIORef (rtasmInfo dflags) (Just v)
  230       return v
  231 
  232 -- See Note [Run-time linker info].
  233 getCompilerInfo' :: Logger -> String -> IO CompilerInfo
  234 getCompilerInfo' logger pgm = do
  235   let -- Try to grab the info from the process output.
  236       parseCompilerInfo _stdo stde _exitc
  237         -- Regular GCC
  238         | any ("gcc version" `isInfixOf`) stde =
  239           return GCC
  240         -- Regular clang
  241         | any ("clang version" `isInfixOf`) stde =
  242           return Clang
  243         -- FreeBSD clang
  244         | any ("FreeBSD clang version" `isInfixOf`) stde =
  245           return Clang
  246         -- Xcode 5.1 clang
  247         | any ("Apple LLVM version 5.1" `isPrefixOf`) stde =
  248           return AppleClang51
  249         -- Xcode 5 clang
  250         | any ("Apple LLVM version" `isPrefixOf`) stde =
  251           return AppleClang
  252         -- Xcode 4.1 clang
  253         | any ("Apple clang version" `isPrefixOf`) stde =
  254           return AppleClang
  255          -- Unknown compiler.
  256         | otherwise = fail $ "invalid -v output, or compiler is unsupported (" ++ pgm ++ "): " ++ unlines stde
  257 
  258   -- Process the executable call
  259   catchIO (do
  260       (exitc, stdo, stde) <-
  261           readProcessEnvWithExitCode pgm ["-v"] c_locale_env
  262       -- Split the output by lines to make certain kinds
  263       -- of processing easier.
  264       parseCompilerInfo (lines stdo) (lines stde) exitc
  265       )
  266       (\err -> do
  267           debugTraceMsg logger 2
  268               (text "Error (figuring out C compiler information):" <+>
  269                text (show err))
  270           errorMsg logger $ hang (text "Warning:") 9 $
  271             text "Couldn't figure out C compiler information!" $$
  272             text "Make sure you're using GNU gcc, or clang"
  273           return UnknownCC
  274       )