summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/ghc.cabal.in4
-rw-r--r--compiler/main/DriverPipeline.hs190
-rw-r--r--compiler/main/SysTools.hs898
-rw-r--r--compiler/main/SysTools/ExtraObj.hs239
-rw-r--r--compiler/main/SysTools/Info.hs256
-rw-r--r--compiler/main/SysTools/Process.hs347
-rw-r--r--compiler/main/SysTools/Tasks.hs343
7 files changed, 1199 insertions, 1078 deletions
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 4f0fbbc90e..d3cbe9563b 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -367,6 +367,10 @@ Library
StaticPtrTable
SysTools
SysTools.Terminal
+ SysTools.ExtraObj
+ SysTools.Info
+ SysTools.Process
+ SysTools.Tasks
Elf
TidyPgm
Ctype
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 4f2cc4c794..199611844c 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -28,7 +28,6 @@ module DriverPipeline (
phaseOutputFilename, getOutputFilename, getPipeState, getPipeEnv,
hscPostBackendPhase, getLocation, setModLocation, setDynFlags,
runPhase, exeFileName,
- mkExtraObjToLinkIntoBinary, mkNoteObjsToLinkIntoBinary,
maybeCreateManifest,
linkingNeeded, checkLinkInfo, writeInterfaceOnlyMode
) where
@@ -37,13 +36,12 @@ module DriverPipeline (
import GhcPrelude
-import AsmUtils
import PipelineMonad
import Packages
import HeaderInfo
import DriverPhases
import SysTools
-import Elf
+import SysTools.ExtraObj
import HscMain
import Finder
import HscTypes hiding ( Hsc )
@@ -476,50 +474,11 @@ linkingNeeded dflags staticLink linkables pkg_deps = do
then return True
else checkLinkInfo dflags pkg_deps exe_file
--- Returns 'False' if it was, and we can avoid linking, because the
--- previous binary was linked with "the same options".
-checkLinkInfo :: DynFlags -> [InstalledUnitId] -> FilePath -> IO Bool
-checkLinkInfo dflags pkg_deps exe_file
- | not (platformSupportsSavingLinkOpts (platformOS (targetPlatform dflags)))
- -- ToDo: Windows and OS X do not use the ELF binary format, so
- -- readelf does not work there. We need to find another way to do
- -- this.
- = return False -- conservatively we should return True, but not
- -- linking in this case was the behaviour for a long
- -- time so we leave it as-is.
- | otherwise
- = do
- link_info <- getLinkInfo dflags pkg_deps
- debugTraceMsg dflags 3 $ text ("Link info: " ++ link_info)
- m_exe_link_info <- readElfNoteAsString dflags exe_file
- ghcLinkInfoSectionName ghcLinkInfoNoteName
- let sameLinkInfo = (Just link_info == m_exe_link_info)
- debugTraceMsg dflags 3 $ case m_exe_link_info of
- Nothing -> text "Exe link info: Not found"
- Just s
- | sameLinkInfo -> text ("Exe link info is the same")
- | otherwise -> text ("Exe link info is different: " ++ s)
- return (not sameLinkInfo)
-
-platformSupportsSavingLinkOpts :: OS -> Bool
-platformSupportsSavingLinkOpts os
- | os == OSSolaris2 = False -- see #5382
- | otherwise = osElfTarget os
-
--- See Note [LinkInfo section]
-ghcLinkInfoSectionName :: String
-ghcLinkInfoSectionName = ".debug-ghc-link-info"
- -- if we use the ".debug" prefix, then strip will strip it by default
-
--- Identifier for the note (see Note [LinkInfo section])
-ghcLinkInfoNoteName :: String
-ghcLinkInfoNoteName = "GHC link info"
-
findHSLib :: DynFlags -> [String] -> String -> IO (Maybe FilePath)
findHSLib dflags dirs lib = do
let batch_lib_file = if WayDyn `notElem` ways dflags
- then "lib" ++ lib <.> "a"
- else mkSOName (targetPlatform dflags) lib
+ then "lib" ++ lib <.> "a"
+ else mkSOName (targetPlatform dflags) lib
found <- filterM doesFileExist (map (</> batch_lib_file) dirs)
case found of
[] -> return Nothing
@@ -1678,143 +1637,6 @@ getLocation src_flavour mod_name = do
| otherwise = location3
return location4
-mkExtraObj :: DynFlags -> Suffix -> String -> IO FilePath
-mkExtraObj dflags extn xs
- = do cFile <- newTempName dflags TFL_CurrentModule extn
- oFile <- newTempName dflags TFL_GhcSession "o"
- writeFile cFile xs
- ccInfo <- liftIO $ getCompilerInfo dflags
- SysTools.runCc dflags
- ([Option "-c",
- FileOption "" cFile,
- Option "-o",
- FileOption "" oFile]
- ++ if extn /= "s"
- then cOpts
- else asmOpts ccInfo)
- return oFile
- where
- -- Pass a different set of options to the C compiler depending one whether
- -- we're compiling C or assembler. When compiling C, we pass the usual
- -- set of include directories and PIC flags.
- cOpts = map Option (picCCOpts dflags)
- ++ map (FileOption "-I")
- (includeDirs $ getPackageDetails dflags rtsUnitId)
-
- -- When compiling assembler code, we drop the usual C options, and if the
- -- compiler is Clang, we add an extra argument to tell Clang to ignore
- -- unused command line options. See trac #11684.
- asmOpts ccInfo =
- if any (ccInfo ==) [Clang, AppleClang, AppleClang51]
- then [Option "-Qunused-arguments"]
- else []
-
-
--- When linking a binary, we need to create a C main() function that
--- starts everything off. This used to be compiled statically as part
--- of the RTS, but that made it hard to change the -rtsopts setting,
--- so now we generate and compile a main() stub as part of every
--- binary and pass the -rtsopts setting directly to the RTS (#5373)
---
-mkExtraObjToLinkIntoBinary :: DynFlags -> IO FilePath
-mkExtraObjToLinkIntoBinary dflags = do
- when (gopt Opt_NoHsMain dflags && haveRtsOptsFlags dflags) $ do
- putLogMsg dflags NoReason SevInfo noSrcSpan
- (defaultUserStyle dflags)
- (text "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." $$
- text " Call hs_init_ghc() from your main() function to set these options.")
-
- mkExtraObj dflags "c" (showSDoc dflags main)
-
- where
- main
- | gopt Opt_NoHsMain dflags = Outputable.empty
- | otherwise = vcat [
- text "#include \"Rts.h\"",
- text "extern StgClosure ZCMain_main_closure;",
- text "int main(int argc, char *argv[])",
- char '{',
- text " RtsConfig __conf = defaultRtsConfig;",
- text " __conf.rts_opts_enabled = "
- <> text (show (rtsOptsEnabled dflags)) <> semi,
- text " __conf.rts_opts_suggestions = "
- <> text (if rtsOptsSuggestions dflags
- then "true"
- else "false") <> semi,
- case rtsOpts dflags of
- Nothing -> Outputable.empty
- Just opts -> text " __conf.rts_opts= " <>
- text (show opts) <> semi,
- text " __conf.rts_hs_main = true;",
- text " return hs_main(argc,argv,&ZCMain_main_closure,__conf);",
- char '}',
- char '\n' -- final newline, to keep gcc happy
- ]
-
--- Write out the link info section into a new assembly file. Previously
--- this was included as inline assembly in the main.c file but this
--- is pretty fragile. gas gets upset trying to calculate relative offsets
--- that span the .note section (notably .text) when debug info is present
-mkNoteObjsToLinkIntoBinary :: DynFlags -> [InstalledUnitId] -> IO [FilePath]
-mkNoteObjsToLinkIntoBinary dflags dep_packages = do
- link_info <- getLinkInfo dflags dep_packages
-
- if (platformSupportsSavingLinkOpts (platformOS (targetPlatform dflags)))
- then fmap (:[]) $ mkExtraObj dflags "s" (showSDoc dflags (link_opts link_info))
- else return []
-
- where
- link_opts info = hcat [
- -- "link info" section (see Note [LinkInfo section])
- makeElfNote ghcLinkInfoSectionName ghcLinkInfoNoteName 0 info,
-
- -- ALL generated assembly must have this section to disable
- -- executable stacks. See also
- -- compiler/nativeGen/AsmCodeGen.hs for another instance
- -- where we need to do this.
- if platformHasGnuNonexecStack (targetPlatform dflags)
- then text ".section .note.GNU-stack,\"\","
- <> sectionType "progbits" <> char '\n'
- else Outputable.empty
- ]
-
--- | Return the "link info" string
---
--- See Note [LinkInfo section]
-getLinkInfo :: DynFlags -> [InstalledUnitId] -> IO String
-getLinkInfo dflags dep_packages = do
- package_link_opts <- getPackageLinkOpts dflags dep_packages
- pkg_frameworks <- if platformUsesFrameworks (targetPlatform dflags)
- then getPackageFrameworks dflags dep_packages
- else return []
- let extra_ld_inputs = ldInputs dflags
- let
- link_info = (package_link_opts,
- pkg_frameworks,
- rtsOpts dflags,
- rtsOptsEnabled dflags,
- gopt Opt_NoHsMain dflags,
- map showOpt extra_ld_inputs,
- getOpts dflags opt_l)
- --
- return (show link_info)
-
-
-{- Note [LinkInfo section]
- ~~~~~~~~~~~~~~~~~~~~~~~
-
-The "link info" is a string representing the parameters of the link. We save
-this information in the binary, and the next time we link, if nothing else has
-changed, we use the link info stored in the existing binary to decide whether
-to re-link or not.
-
-The "link info" string is stored in a ELF section called ".debug-ghc-link-info"
-(see ghcLinkInfoSectionName) with the SHT_NOTE type. For some time, it used to
-not follow the specified record-based format (see #11022).
-
--}
-
-
-----------------------------------------------------------------------------
-- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
@@ -2379,12 +2201,6 @@ touchObjectFile dflags path = do
createDirectoryIfMissing True $ takeDirectory path
SysTools.touch dflags "Touching object file" path
-haveRtsOptsFlags :: DynFlags -> Bool
-haveRtsOptsFlags dflags =
- isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of
- RtsOptsSafeOnly -> False
- _ -> True
-
-- | Find out path to @ghcversion.h@ file
getGhcVersionPathName :: DynFlags -> IO FilePath
getGhcVersionPathName dflags = do
diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs
index 96a6f1764c..21ed03b407 100644
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -16,26 +16,11 @@ module SysTools (
initLlvmTargets,
-- Interface to system tools
- runUnlit, runCpp, runCc, -- [Option] -> IO ()
- runPp, -- [Option] -> IO ()
- runSplit, -- [Option] -> IO ()
- runAs, runLink, runLibtool, -- [Option] -> IO ()
- runAr, askAr, runRanlib,
- runMkDLL,
- runWindres,
- runLlvmOpt,
- runLlvmLlc,
- runClang,
- figureLlvmVersion,
-
- getLinkerInfo,
- getCompilerInfo,
+ module SysTools.Tasks,
+ module SysTools.Info,
linkDynLib,
- askLd,
-
- touch, -- String -> String -> IO ()
copy,
copyWithHeader,
@@ -62,19 +47,13 @@ import Panic
import Platform
import Util
import DynFlags
-import Exception
-import FileCleanup
-import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion)
-
-import Data.IORef
-import System.Exit
-import System.Environment
import System.FilePath
import System.IO
-import System.IO.Error as IO
import System.Directory
-import Data.Char
+import SysTools.ExtraObj
+import SysTools.Info
+import SysTools.Tasks
import Data.List
#if defined(mingw32_HOST_OS)
@@ -83,6 +62,8 @@ import qualified System.Win32.Types as Win32
#else
import qualified System.Win32.Info as Win32
#endif
+import Data.Char
+import Exception
import Foreign
import Foreign.C.String
import System.Win32.Types (DWORD, LPTSTR, HANDLE)
@@ -91,11 +72,6 @@ import System.Win32.File (createFile,closeHandle, gENERIC_READ, fILE_SHARE_READ,
import System.Win32.DLL (loadLibrary, getProcAddress)
#endif
-import System.Process
-import Control.Concurrent
-import FastString
-import SrcLoc ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan )
-
#if defined(mingw32_HOST_OS)
# if defined(i386_HOST_ARCH)
# define WINDOWS_CCONV stdcall
@@ -403,263 +379,6 @@ findTopDir Nothing
Nothing -> throwGhcExceptionIO (InstallationError "missing -B<dir> option")
Just dir -> return dir
-{-
-************************************************************************
-* *
-\subsection{Running an external program}
-* *
-************************************************************************
--}
-
-runUnlit :: DynFlags -> [Option] -> IO ()
-runUnlit dflags args = do
- let prog = pgm_L dflags
- opts = getOpts dflags opt_L
- runSomething dflags "Literate pre-processor" prog
- (map Option opts ++ args)
-
-runCpp :: DynFlags -> [Option] -> IO ()
-runCpp dflags args = do
- let (p,args0) = pgm_P dflags
- args1 = map Option (getOpts dflags opt_P)
- args2 = [Option "-Werror" | gopt Opt_WarnIsError dflags]
- ++ [Option "-Wundef" | wopt Opt_WarnCPPUndef dflags]
- mb_env <- getGccEnv args2
- runSomethingFiltered dflags id "C pre-processor" p
- (args0 ++ args1 ++ args2 ++ args) Nothing mb_env
-
-runPp :: DynFlags -> [Option] -> IO ()
-runPp dflags args = do
- let prog = pgm_F dflags
- opts = map Option (getOpts dflags opt_F)
- runSomething dflags "Haskell pre-processor" prog (args ++ opts)
-
-runCc :: DynFlags -> [Option] -> IO ()
-runCc dflags args = do
- let (p,args0) = pgm_c dflags
- args1 = map Option (getOpts dflags opt_c)
- args2 = args0 ++ args1 ++ args
- mb_env <- getGccEnv args2
- runSomethingResponseFile dflags cc_filter "C Compiler" p args2 mb_env
- where
- -- discard some harmless warnings from gcc that we can't turn off
- cc_filter = unlines . doFilter . lines
-
- {-
- gcc gives warnings in chunks like so:
- In file included from /foo/bar/baz.h:11,
- from /foo/bar/baz2.h:22,
- from wibble.c:33:
- /foo/flibble:14: global register variable ...
- /foo/flibble:15: warning: call-clobbered r...
- We break it up into its chunks, remove any call-clobbered register
- warnings from each chunk, and then delete any chunks that we have
- emptied of warnings.
- -}
- doFilter = unChunkWarnings . filterWarnings . chunkWarnings []
- -- We can't assume that the output will start with an "In file inc..."
- -- line, so we start off expecting a list of warnings rather than a
- -- location stack.
- chunkWarnings :: [String] -- The location stack to use for the next
- -- list of warnings
- -> [String] -- The remaining lines to look at
- -> [([String], [String])]
- chunkWarnings loc_stack [] = [(loc_stack, [])]
- chunkWarnings loc_stack xs
- = case break loc_stack_start xs of
- (warnings, lss:xs') ->
- case span loc_start_continuation xs' of
- (lsc, xs'') ->
- (loc_stack, warnings) : chunkWarnings (lss : lsc) xs''
- _ -> [(loc_stack, xs)]
-
- filterWarnings :: [([String], [String])] -> [([String], [String])]
- filterWarnings [] = []
- -- If the warnings are already empty then we are probably doing
- -- something wrong, so don't delete anything
- filterWarnings ((xs, []) : zs) = (xs, []) : filterWarnings zs
- filterWarnings ((xs, ys) : zs) = case filter wantedWarning ys of
- [] -> filterWarnings zs
- ys' -> (xs, ys') : filterWarnings zs
-
- unChunkWarnings :: [([String], [String])] -> [String]
- unChunkWarnings [] = []
- unChunkWarnings ((xs, ys) : zs) = xs ++ ys ++ unChunkWarnings zs
-
- loc_stack_start s = "In file included from " `isPrefixOf` s
- loc_start_continuation s = " from " `isPrefixOf` s
- wantedWarning w
- | "warning: call-clobbered register used" `isContainedIn` w = False
- | otherwise = True
-
-isContainedIn :: String -> String -> Bool
-xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
-
--- | Run the linker with some arguments and return the output
-askLd :: DynFlags -> [Option] -> IO String
-askLd dflags args = do
- let (p,args0) = pgm_l dflags
- args1 = map Option (getOpts dflags opt_l)
- args2 = args0 ++ args1 ++ args
- mb_env <- getGccEnv args2
- runSomethingWith dflags "gcc" p args2 $ \real_args ->
- readCreateProcessWithExitCode' (proc p real_args){ env = mb_env }
-
--- Similar to System.Process.readCreateProcessWithExitCode, but stderr is
--- inherited from the parent process, and output to stderr is not captured.
-readCreateProcessWithExitCode'
- :: CreateProcess
- -> IO (ExitCode, String) -- ^ stdout
-readCreateProcessWithExitCode' proc = do
- (_, Just outh, _, pid) <-
- createProcess proc{ std_out = CreatePipe }
-
- -- fork off a thread to start consuming the output
- output <- hGetContents outh
- outMVar <- newEmptyMVar
- _ <- forkIO $ evaluate (length output) >> putMVar outMVar ()
-
- -- wait on the output
- takeMVar outMVar
- hClose outh
-
- -- wait on the process
- ex <- waitForProcess pid
-
- return (ex, output)
-
-replaceVar :: (String, String) -> [(String, String)] -> [(String, String)]
-replaceVar (var, value) env =
- (var, value) : filter (\(var',_) -> var /= var') env
-
--- | Version of @System.Process.readProcessWithExitCode@ that takes a
--- key-value tuple to insert into the environment.
-readProcessEnvWithExitCode
- :: String -- ^ program path
- -> [String] -- ^ program args
- -> (String, String) -- ^ addition to the environment
- -> IO (ExitCode, String, String) -- ^ (exit_code, stdout, stderr)
-readProcessEnvWithExitCode prog args env_update = do
- current_env <- getEnvironment
- readCreateProcessWithExitCode (proc prog args) {
- env = Just (replaceVar env_update current_env) } ""
-
--- Don't let gcc localize version info string, #8825
-c_locale_env :: (String, String)
-c_locale_env = ("LANGUAGE", "C")
-
--- If the -B<dir> option is set, add <dir> to PATH. This works around
--- a bug in gcc on Windows Vista where it can't find its auxiliary
--- binaries (see bug #1110).
-getGccEnv :: [Option] -> IO (Maybe [(String,String)])
-getGccEnv opts =
- if null b_dirs
- then return Nothing
- else do env <- getEnvironment
- return (Just (map mangle_path env))
- where
- (b_dirs, _) = partitionWith get_b_opt opts
-
- get_b_opt (Option ('-':'B':dir)) = Left dir
- get_b_opt other = Right other
-
- mangle_path (path,paths) | map toUpper path == "PATH"
- = (path, '\"' : head b_dirs ++ "\";" ++ paths)
- mangle_path other = other
-
-runSplit :: DynFlags -> [Option] -> IO ()
-runSplit dflags args = do
- let (p,args0) = pgm_s dflags
- runSomething dflags "Splitter" p (args0++args)
-
-runAs :: DynFlags -> [Option] -> IO ()
-runAs dflags args = do
- let (p,args0) = pgm_a dflags
- args1 = map Option (getOpts dflags opt_a)
- args2 = args0 ++ args1 ++ args
- mb_env <- getGccEnv args2
- runSomethingFiltered dflags id "Assembler" p args2 Nothing mb_env
-
--- | Run the LLVM Optimiser
-runLlvmOpt :: DynFlags -> [Option] -> IO ()
-runLlvmOpt dflags args = do
- let (p,args0) = pgm_lo dflags
- args1 = map Option (getOpts dflags opt_lo)
- runSomething dflags "LLVM Optimiser" p (args0 ++ args1 ++ args)
-
--- | Run the LLVM Compiler
-runLlvmLlc :: DynFlags -> [Option] -> IO ()
-runLlvmLlc dflags args = do
- let (p,args0) = pgm_lc dflags
- args1 = map Option (getOpts dflags opt_lc)
- runSomething dflags "LLVM Compiler" p (args0 ++ args1 ++ args)
-
--- | Run the clang compiler (used as an assembler for the LLVM
--- backend on OS X as LLVM doesn't support the OS X system
--- assembler)
-runClang :: DynFlags -> [Option] -> IO ()
-runClang dflags args = do
- let (clang,_) = pgm_lcc dflags
- -- be careful what options we call clang with
- -- see #5903 and #7617 for bugs caused by this.
- (_,args0) = pgm_a dflags
- args1 = map Option (getOpts dflags opt_a)
- args2 = args0 ++ args1 ++ args
- mb_env <- getGccEnv args2
- Exception.catch (do
- runSomethingFiltered dflags id "Clang (Assembler)" clang args2 Nothing mb_env
- )
- (\(err :: SomeException) -> do
- errorMsg dflags $
- text ("Error running clang! you need clang installed to use the" ++
- " LLVM backend") $+$
- text "(or GHC tried to execute clang incorrectly)"
- throwIO err
- )
-
--- | Figure out which version of LLVM we are running this session
-figureLlvmVersion :: DynFlags -> IO (Maybe (Int, Int))
-figureLlvmVersion dflags = do
- let (pgm,opts) = pgm_lc dflags
- args = filter notNull (map showOpt opts)
- -- we grab the args even though they should be useless just in
- -- case the user is using a customised 'llc' that requires some
- -- of the options they've specified. llc doesn't care what other
- -- options are specified when '-version' is used.
- args' = args ++ ["-version"]
- ver <- catchIO (do
- (pin, pout, perr, _) <- runInteractiveProcess pgm args'
- Nothing Nothing
- {- > llc -version
- LLVM (http://llvm.org/):
- LLVM version 3.5.2
- ...
- -}
- hSetBinaryMode pout False
- _ <- hGetLine pout
- vline <- dropWhile (not . isDigit) `fmap` hGetLine pout
- v <- case span (/= '.') vline of
- ("",_) -> fail "no digits!"
- (x,y) -> return (read x
- , read $ takeWhile isDigit $ drop 1 y)
-
- hClose pin
- hClose pout
- hClose perr
- return $ Just v
- )
- (\err -> do
- debugTraceMsg dflags 2
- (text "Error (figuring out LLVM version):" <+>
- text (show err))
- errorMsg dflags $ vcat
- [ text "Warning:", nest 9 $
- text "Couldn't figure out LLVM version!" $$
- text ("Make sure you have installed LLVM " ++
- llvmVersionStr supportedLlvmVersion) ]
- return Nothing)
- return ver
-
{- Note [Windows stack usage]
See: Trac #8870 (and #8834 for related info) and #12186
@@ -691,356 +410,6 @@ for more information.
-}
-{- Note [Run-time linker info]
-
-See also: Trac #5240, Trac #6063, Trac #10110
-
-Before 'runLink', we need to be sure to get the relevant information
-about the linker we're using at runtime to see if we need any extra
-options. For example, GNU ld requires '--reduce-memory-overheads' and
-'--hash-size=31' in order to use reasonable amounts of memory (see
-trac #5240.) But this isn't supported in GNU gold.
-
-Generally, the linker changing from what was detected at ./configure
-time has always been possible using -pgml, but on Linux it can happen
-'transparently' by installing packages like binutils-gold, which
-change what /usr/bin/ld actually points to.
-
-Clang vs GCC notes:
-
-For gcc, 'gcc -Wl,--version' gives a bunch of output about how to
-invoke the linker before the version information string. For 'clang',
-the version information for 'ld' is all that's output. For this
-reason, we typically need to slurp up all of the standard error output
-and look through it.
-
-Other notes:
-
-We cache the LinkerInfo inside DynFlags, since clients may link
-multiple times. The definition of LinkerInfo is there to avoid a
-circular dependency.
-
--}
-
-{- Note [ELF needed shared libs]
-
-Some distributions change the link editor's default handling of
-ELF DT_NEEDED tags to include only those shared objects that are
-needed to resolve undefined symbols. For Template Haskell we need
-the last temporary shared library also if it is not needed for the
-currently linked temporary shared library. We specify --no-as-needed
-to override the default. This flag exists in GNU ld and GNU gold.
-
-The flag is only needed on ELF systems. On Windows (PE) and Mac OS X
-(Mach-O) the flag is not needed.
-
--}
-
-{- Note [Windows static libGCC]
-
-The GCC versions being upgraded to in #10726 are configured with
-dynamic linking of libgcc supported. This results in libgcc being
-linked dynamically when a shared library is created.
-
-This introduces thus an extra dependency on GCC dll that was not
-needed before by shared libraries created with GHC. This is a particular
-issue on Windows because you get a non-obvious error due to this missing
-dependency. This dependent dll is also not commonly on your path.
-
-For this reason using the static libgcc is preferred as it preserves
-the same behaviour that existed before. There are however some very good
-reasons to have the shared version as well as described on page 181 of
-https://gcc.gnu.org/onlinedocs/gcc-5.2.0/gcc.pdf :
-
-"There are several situations in which an application should use the
- shared ‘libgcc’ instead of the static version. The most common of these
- is when the application wishes to throw and catch exceptions across different
- shared libraries. In that case, each of the libraries as well as the application
- itself should use the shared ‘libgcc’. "
-
--}
-
-neededLinkArgs :: LinkerInfo -> [Option]
-neededLinkArgs (GnuLD o) = o
-neededLinkArgs (GnuGold o) = o
-neededLinkArgs (DarwinLD o) = o
-neededLinkArgs (SolarisLD o) = o
-neededLinkArgs (AixLD o) = o
-neededLinkArgs UnknownLD = []
-
--- Grab linker info and cache it in DynFlags.
-getLinkerInfo :: DynFlags -> IO LinkerInfo
-getLinkerInfo dflags = do
- info <- readIORef (rtldInfo dflags)
- case info of
- Just v -> return v
- Nothing -> do
- v <- getLinkerInfo' dflags
- writeIORef (rtldInfo dflags) (Just v)
- return v
-
--- See Note [Run-time linker info].
-getLinkerInfo' :: DynFlags -> IO LinkerInfo
-getLinkerInfo' dflags = do
- let platform = targetPlatform dflags
- os = platformOS platform
- (pgm,args0) = pgm_l dflags
- args1 = map Option (getOpts dflags opt_l)
- args2 = args0 ++ args1
- args3 = filter notNull (map showOpt args2)
-
- -- Try to grab the info from the process output.
- parseLinkerInfo stdo _stde _exitc
- | any ("GNU ld" `isPrefixOf`) stdo =
- -- GNU ld specifically needs to use less memory. This especially
- -- hurts on small object files. Trac #5240.
- -- Set DT_NEEDED for all shared libraries. Trac #10110.
- -- TODO: Investigate if these help or hurt when using split sections.
- return (GnuLD $ map Option ["-Wl,--hash-size=31",
- "-Wl,--reduce-memory-overheads",
- -- ELF specific flag
- -- see Note [ELF needed shared libs]
- "-Wl,--no-as-needed"])
-
- | any ("GNU gold" `isPrefixOf`) stdo =
- -- GNU gold only needs --no-as-needed. Trac #10110.
- -- ELF specific flag, see Note [ELF needed shared libs]
- return (GnuGold [Option "-Wl,--no-as-needed"])
-
- -- Unknown linker.
- | otherwise = fail "invalid --version output, or linker is unsupported"
-
- -- Process the executable call
- info <- catchIO (do
- case os of
- OSSolaris2 ->
- -- Solaris uses its own Solaris linker. Even all
- -- GNU C are recommended to configure with Solaris
- -- linker instead of using GNU binutils linker. Also
- -- all GCC distributed with Solaris follows this rule
- -- precisely so we assume here, the Solaris linker is
- -- used.
- return $ SolarisLD []
- OSAIX ->
- -- IBM AIX uses its own non-binutils linker as well
- return $ AixLD []
- OSDarwin ->
- -- Darwin has neither GNU Gold or GNU LD, but a strange linker
- -- that doesn't support --version. We can just assume that's
- -- what we're using.
- return $ DarwinLD []
- OSMinGW32 ->
- -- GHC doesn't support anything but GNU ld on Windows anyway.
- -- Process creation is also fairly expensive on win32, so
- -- we short-circuit here.
- return $ GnuLD $ map Option
- [ -- Reduce ld memory usage
- "-Wl,--hash-size=31"
- , "-Wl,--reduce-memory-overheads"
- -- Emit gcc stack checks
- -- Note [Windows stack usage]
- , "-fstack-check"
- -- Force static linking of libGCC
- -- Note [Windows static libGCC]
- , "-static-libgcc" ]
- _ -> do
- -- In practice, we use the compiler as the linker here. Pass
- -- -Wl,--version to get linker version info.
- (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm
- (["-Wl,--version"] ++ args3)
- c_locale_env
- -- Split the output by lines to make certain kinds
- -- of processing easier. In particular, 'clang' and 'gcc'
- -- have slightly different outputs for '-Wl,--version', but
- -- it's still easy to figure out.
- parseLinkerInfo (lines stdo) (lines stde) exitc
- )
- (\err -> do
- debugTraceMsg dflags 2
- (text "Error (figuring out linker information):" <+>
- text (show err))
- errorMsg dflags $ hang (text "Warning:") 9 $
- text "Couldn't figure out linker information!" $$
- text "Make sure you're using GNU ld, GNU gold" <+>
- text "or the built in OS X linker, etc."
- return UnknownLD)
- return info
-
--- Grab compiler info and cache it in DynFlags.
-getCompilerInfo :: DynFlags -> IO CompilerInfo
-getCompilerInfo dflags = do
- info <- readIORef (rtccInfo dflags)
- case info of
- Just v -> return v
- Nothing -> do
- v <- getCompilerInfo' dflags
- writeIORef (rtccInfo dflags) (Just v)
- return v
-
--- See Note [Run-time linker info].
-getCompilerInfo' :: DynFlags -> IO CompilerInfo
-getCompilerInfo' dflags = do
- let (pgm,_) = pgm_c dflags
- -- Try to grab the info from the process output.
- parseCompilerInfo _stdo stde _exitc
- -- Regular GCC
- | any ("gcc version" `isInfixOf`) stde =
- return GCC
- -- Regular clang
- | any ("clang version" `isInfixOf`) stde =
- return Clang
- -- FreeBSD clang
- | any ("FreeBSD clang version" `isInfixOf`) stde =
- return Clang
- -- XCode 5.1 clang
- | any ("Apple LLVM version 5.1" `isPrefixOf`) stde =
- return AppleClang51
- -- XCode 5 clang
- | any ("Apple LLVM version" `isPrefixOf`) stde =
- return AppleClang
- -- XCode 4.1 clang
- | any ("Apple clang version" `isPrefixOf`) stde =
- return AppleClang
- -- Unknown linker.
- | otherwise = fail "invalid -v output, or compiler is unsupported"
-
- -- Process the executable call
- info <- catchIO (do
- (exitc, stdo, stde) <-
- readProcessEnvWithExitCode pgm ["-v"] c_locale_env
- -- Split the output by lines to make certain kinds
- -- of processing easier.
- parseCompilerInfo (lines stdo) (lines stde) exitc
- )
- (\err -> do
- debugTraceMsg dflags 2
- (text "Error (figuring out C compiler information):" <+>
- text (show err))
- errorMsg dflags $ hang (text "Warning:") 9 $
- text "Couldn't figure out C compiler information!" $$
- text "Make sure you're using GNU gcc, or clang"
- return UnknownCC)
- return info
-
-runLink :: DynFlags -> [Option] -> IO ()
-runLink dflags args = do
- -- See Note [Run-time linker info]
- linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags
- let (p,args0) = pgm_l dflags
- args1 = map Option (getOpts dflags opt_l)
- args2 = args0 ++ linkargs ++ args1 ++ args
- mb_env <- getGccEnv args2
- runSomethingResponseFile 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
- symbols 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
- choose 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 the 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 the 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
- linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags
- let args1 = map Option (getOpts dflags opt_l)
- args2 = [Option "-static"] ++ args1 ++ args ++ linkargs
- libtool = pgm_libtool dflags
- mb_env <- getGccEnv args2
- runSomethingFiltered dflags id "Linker" libtool args2 Nothing mb_env
-
-runAr :: DynFlags -> Maybe FilePath -> [Option] -> IO ()
-runAr dflags cwd args = do
- let ar = pgm_ar dflags
- runSomethingFiltered dflags id "Ar" ar args cwd Nothing
-
-askAr :: DynFlags -> Maybe FilePath -> [Option] -> IO String
-askAr dflags mb_cwd args = do
- let ar = pgm_ar dflags
- runSomethingWith dflags "Ar" ar args $ \real_args ->
- readCreateProcessWithExitCode' (proc ar real_args){ cwd = mb_cwd }
-
-runRanlib :: DynFlags -> [Option] -> IO ()
-runRanlib dflags args = do
- let ranlib = pgm_ranlib dflags
- runSomethingFiltered dflags id "Ranlib" ranlib args Nothing Nothing
-
-runMkDLL :: DynFlags -> [Option] -> IO ()
-runMkDLL dflags args = do
- let (p,args0) = pgm_dll dflags
- args1 = args0 ++ args
- mb_env <- getGccEnv (args0++args)
- runSomethingFiltered dflags id "Make DLL" p args1 Nothing mb_env
-
-runWindres :: DynFlags -> [Option] -> IO ()
-runWindres dflags args = do
- let (gcc, gcc_args) = pgm_c dflags
- windres = pgm_windres dflags
- opts = map Option (getOpts dflags opt_windres)
- quote x = "\"" ++ x ++ "\""
- args' = -- If windres.exe and gcc.exe are in a directory containing
- -- spaces then windres fails to run gcc. We therefore need
- -- to tell it what command to use...
- Option ("--preprocessor=" ++
- unwords (map quote (gcc :
- map showOpt gcc_args ++
- map showOpt opts ++
- ["-E", "-xc", "-DRC_INVOKED"])))
- -- ...but if we do that then if windres calls popen then
- -- it can't understand the quoting, so we have to use
- -- --use-temp-file so that it interprets it correctly.
- -- See #1828.
- : Option "--use-temp-file"
- : args
- mb_env <- getGccEnv gcc_args
- runSomethingFiltered dflags id "Windres" windres args' Nothing mb_env
-
-touch :: DynFlags -> String -> String -> IO ()
-touch dflags purpose arg =
- runSomething dflags purpose (pgm_T dflags) [FileOption "" arg]
-
copy :: DynFlags -> String -> FilePath -> FilePath -> IO ()
copy dflags purpose from to = copyWithHeader dflags purpose Nothing from to
@@ -1065,240 +434,6 @@ copyWithHeader dflags purpose maybe_header from to = do
hPutStr h str
hSetBinaryMode h True
------------------------------------------------------------------------------
--- Running an external program
-
-runSomething :: DynFlags
- -> String -- For -v message
- -> String -- Command name (possibly a full path)
- -- assumed already dos-ified
- -> [Option] -- Arguments
- -- runSomething will dos-ify them
- -> IO ()
-
-runSomething dflags phase_name pgm args =
- runSomethingFiltered dflags id phase_name pgm args Nothing Nothing
-
--- | Run a command, placing the arguments in an external response file.
---
--- This command is used in order to avoid overlong command line arguments on
--- Windows. The command line arguments are first written to an external,
--- temporary response file, and then passed to the linker via @filepath.
--- response files for passing them in. See:
---
--- https://gcc.gnu.org/wiki/Response_Files
--- https://ghc.haskell.org/trac/ghc/ticket/10777
-runSomethingResponseFile
- :: DynFlags -> (String->String) -> String -> String -> [Option]
- -> Maybe [(String,String)] -> IO ()
-
-runSomethingResponseFile dflags filter_fn phase_name pgm args mb_env =
- runSomethingWith dflags phase_name pgm args $ \real_args -> do
- fp <- getResponseFile real_args
- let args = ['@':fp]
- r <- builderMainLoop dflags filter_fn pgm args Nothing mb_env
- return (r,())
- where
- getResponseFile args = do
- fp <- newTempName dflags TFL_CurrentModule "rsp"
- withFile fp WriteMode $ \h -> do
-#if defined(mingw32_HOST_OS)
- hSetEncoding h latin1
-#else
- hSetEncoding h utf8
-#endif
- hPutStr h $ unlines $ map escape args
- return fp
-
- -- Note: Response files have backslash-escaping, double quoting, and are
- -- whitespace separated (some implementations use newline, others any
- -- whitespace character). Therefore, escape any backslashes, newlines, and
- -- double quotes in the argument, and surround the content with double
- -- quotes.
- --
- -- Another possibility that could be considered would be to convert
- -- backslashes in the argument to forward slashes. This would generally do
- -- the right thing, since backslashes in general only appear in arguments
- -- as part of file paths on Windows, and the forward slash is accepted for
- -- those. However, escaping is more reliable, in case somehow a backslash
- -- appears in a non-file.
- escape x = concat
- [ "\""
- , concatMap
- (\c ->
- case c of
- '\\' -> "\\\\"
- '\n' -> "\\n"
- '\"' -> "\\\""
- _ -> [c])
- x
- , "\""
- ]
-
-runSomethingFiltered
- :: DynFlags -> (String->String) -> String -> String -> [Option]
- -> Maybe FilePath -> Maybe [(String,String)] -> IO ()
-
-runSomethingFiltered dflags filter_fn phase_name pgm args mb_cwd mb_env = do
- runSomethingWith dflags phase_name pgm args $ \real_args -> do
- r <- builderMainLoop dflags filter_fn pgm real_args mb_cwd mb_env
- return (r,())
-
-runSomethingWith
- :: DynFlags -> String -> String -> [Option]
- -> ([String] -> IO (ExitCode, a))
- -> IO a
-
-runSomethingWith dflags phase_name pgm args io = do
- let real_args = filter notNull (map showOpt args)
- cmdLine = showCommandForUser pgm real_args
- traceCmd dflags phase_name cmdLine $ handleProc pgm phase_name $ io real_args
-
-handleProc :: String -> String -> IO (ExitCode, r) -> IO r
-handleProc pgm phase_name proc = do
- (rc, r) <- proc `catchIO` handler
- case rc of
- ExitSuccess{} -> return r
- ExitFailure n -> throwGhcExceptionIO (
- ProgramError ("`" ++ takeFileName pgm ++ "'" ++
- " failed in phase `" ++ phase_name ++ "'." ++
- " (Exit code: " ++ show n ++ ")"))
- where
- handler err =
- if IO.isDoesNotExistError err
- then does_not_exist
- else throwGhcExceptionIO (ProgramError $ show err)
-
- does_not_exist = throwGhcExceptionIO (InstallationError ("could not execute: " ++ pgm))
-
-
-builderMainLoop :: DynFlags -> (String -> String) -> FilePath
- -> [String] -> Maybe FilePath -> Maybe [(String, String)]
- -> IO ExitCode
-builderMainLoop dflags filter_fn pgm real_args mb_cwd mb_env = do
- chan <- newChan
-
- -- We use a mask here rather than a bracket because we want
- -- to distinguish between cleaning up with and without an
- -- exception. This is to avoid calling terminateProcess
- -- unless an exception was raised.
- let safely inner = mask $ \restore -> do
- -- acquire
- (hStdIn, hStdOut, hStdErr, hProcess) <- restore $
- runInteractiveProcess pgm real_args mb_cwd mb_env
- let cleanup_handles = do
- hClose hStdIn
- hClose hStdOut
- hClose hStdErr
- r <- try $ restore $ do
- hSetBuffering hStdOut LineBuffering
- hSetBuffering hStdErr LineBuffering
- let make_reader_proc h = forkIO $ readerProc chan h filter_fn
- bracketOnError (make_reader_proc hStdOut) killThread $ \_ ->
- bracketOnError (make_reader_proc hStdErr) killThread $ \_ ->
- inner hProcess
- case r of
- -- onException
- Left (SomeException e) -> do
- terminateProcess hProcess
- cleanup_handles
- throw e
- -- cleanup when there was no exception
- Right s -> do
- cleanup_handles
- return s
- safely $ \h -> do
- -- we don't want to finish until 2 streams have been complete
- -- (stdout and stderr)
- log_loop chan (2 :: Integer)
- -- after that, we wait for the process to finish and return the exit code.
- waitForProcess h
- where
- -- t starts at the number of streams we're listening to (2) decrements each
- -- time a reader process sends EOF. We are safe from looping forever if a
- -- reader thread dies, because they send EOF in a finally handler.
- log_loop _ 0 = return ()
- log_loop chan t = do
- msg <- readChan chan
- case msg of
- BuildMsg msg -> do
- putLogMsg dflags NoReason SevInfo noSrcSpan
- (defaultUserStyle dflags) msg
- log_loop chan t
- BuildError loc msg -> do
- putLogMsg dflags NoReason SevError (mkSrcSpan loc loc)
- (defaultUserStyle dflags) msg
- log_loop chan t
- EOF ->
- log_loop chan (t-1)
-
-readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO ()
-readerProc chan hdl filter_fn =
- (do str <- hGetContents hdl
- loop (linesPlatform (filter_fn str)) Nothing)
- `finally`
- writeChan chan EOF
- -- ToDo: check errors more carefully
- -- ToDo: in the future, the filter should be implemented as
- -- a stream transformer.
- where
- loop [] Nothing = return ()
- loop [] (Just err) = writeChan chan err
- loop (l:ls) in_err =
- case in_err of
- Just err@(BuildError srcLoc msg)
- | leading_whitespace l -> do
- loop ls (Just (BuildError srcLoc (msg $$ text l)))
- | otherwise -> do
- writeChan chan err
- checkError l ls
- Nothing -> do
- checkError l ls
- _ -> panic "readerProc/loop"
-
- checkError l ls
- = case parseError l of
- Nothing -> do
- writeChan chan (BuildMsg (text l))
- loop ls Nothing
- Just (file, lineNum, colNum, msg) -> do
- let srcLoc = mkSrcLoc (mkFastString file) lineNum colNum
- loop ls (Just (BuildError srcLoc (text msg)))
-
- leading_whitespace [] = False
- leading_whitespace (x:_) = isSpace x
-
-parseError :: String -> Maybe (String, Int, Int, String)
-parseError s0 = case breakColon s0 of
- Just (filename, s1) ->
- case breakIntColon s1 of
- Just (lineNum, s2) ->
- case breakIntColon s2 of
- Just (columnNum, s3) ->
- Just (filename, lineNum, columnNum, s3)
- Nothing ->
- Just (filename, lineNum, 0, s2)
- Nothing -> Nothing
- Nothing -> Nothing
-
-breakColon :: String -> Maybe (String, String)
-breakColon xs = case break (':' ==) xs of
- (ys, _:zs) -> Just (ys, zs)
- _ -> Nothing
-
-breakIntColon :: String -> Maybe (Int, String)
-breakIntColon xs = case break (':' ==) xs of
- (ys, _:zs)
- | not (null ys) && all isAscii ys && all isDigit ys ->
- Just (read ys, zs)
- _ -> Nothing
-
-data BuildMessage
- = BuildMsg !SDoc
- | BuildError !SrcLoc !SDoc
- | EOF
-
-
{-
************************************************************************
* *
@@ -1399,25 +534,6 @@ foreign import WINDOWS_CCONV unsafe "dynamic"
getBaseDir = return Nothing
#endif
-
--- Divvy up text stream into lines, taking platform dependent
--- line termination into account.
-linesPlatform :: String -> [String]
-#if !defined(mingw32_HOST_OS)
-linesPlatform ls = lines ls
-#else
-linesPlatform "" = []
-linesPlatform xs =
- case lineBreak xs of
- (as,xs1) -> as : linesPlatform xs1
- where
- lineBreak "" = ("","")
- lineBreak ('\r':'\n':xs) = ([],xs)
- lineBreak ('\n':xs) = ([],xs)
- lineBreak (x:xs) = let (as,bs) = lineBreak xs in (x:as,bs)
-
-#endif
-
linkDynLib :: DynFlags -> [String] -> [InstalledUnitId] -> IO ()
linkDynLib dflags0 o_files dep_packages
= do
diff --git a/compiler/main/SysTools/ExtraObj.hs b/compiler/main/SysTools/ExtraObj.hs
new file mode 100644
index 0000000000..bbcb1b6a7a
--- /dev/null
+++ b/compiler/main/SysTools/ExtraObj.hs
@@ -0,0 +1,239 @@
+-----------------------------------------------------------------------------
+--
+-- GHC Extra object linking code
+--
+-- (c) The GHC Team 2017
+--
+-----------------------------------------------------------------------------
+
+module SysTools.ExtraObj (
+ mkExtraObj, mkExtraObjToLinkIntoBinary, mkNoteObjsToLinkIntoBinary,
+ checkLinkInfo, getLinkInfo, getCompilerInfo,
+ ghcLinkInfoSectionName, ghcLinkInfoNoteName, platformSupportsSavingLinkOpts,
+ haveRtsOptsFlags
+) where
+
+import AsmUtils
+import ErrUtils
+import DynFlags
+import Packages
+import Platform
+import Outputable
+import SrcLoc ( noSrcSpan )
+import Module
+import Elf
+import Util
+import GhcPrelude
+
+import Control.Monad
+import Data.Maybe
+
+import Control.Monad.IO.Class
+
+import FileCleanup
+import SysTools.Tasks
+import SysTools.Info
+
+mkExtraObj :: DynFlags -> Suffix -> String -> IO FilePath
+mkExtraObj dflags extn xs
+ = do cFile <- newTempName dflags TFL_CurrentModule extn
+ oFile <- newTempName dflags TFL_GhcSession "o"
+ writeFile cFile xs
+ ccInfo <- liftIO $ getCompilerInfo dflags
+ runCc dflags
+ ([Option "-c",
+ FileOption "" cFile,
+ Option "-o",
+ FileOption "" oFile]
+ ++ if extn /= "s"
+ then cOpts
+ else asmOpts ccInfo)
+ return oFile
+ where
+ -- Pass a different set of options to the C compiler depending one whether
+ -- we're compiling C or assembler. When compiling C, we pass the usual
+ -- set of include directories and PIC flags.
+ cOpts = map Option (picCCOpts dflags)
+ ++ map (FileOption "-I")
+ (includeDirs $ getPackageDetails dflags rtsUnitId)
+
+ -- When compiling assembler code, we drop the usual C options, and if the
+ -- compiler is Clang, we add an extra argument to tell Clang to ignore
+ -- unused command line options. See trac #11684.
+ asmOpts ccInfo =
+ if any (ccInfo ==) [Clang, AppleClang, AppleClang51]
+ then [Option "-Qunused-arguments"]
+ else []
+
+-- When linking a binary, we need to create a C main() function that
+-- starts everything off. This used to be compiled statically as part
+-- of the RTS, but that made it hard to change the -rtsopts setting,
+-- so now we generate and compile a main() stub as part of every
+-- binary and pass the -rtsopts setting directly to the RTS (#5373)
+--
+-- On Windows, when making a shared library we also may need a DllMain.
+--
+mkExtraObjToLinkIntoBinary :: DynFlags -> IO FilePath
+mkExtraObjToLinkIntoBinary dflags = do
+ when (gopt Opt_NoHsMain dflags && haveRtsOptsFlags dflags) $ do
+ putLogMsg dflags NoReason SevInfo noSrcSpan
+ (defaultUserStyle dflags)
+ (text "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." $$
+ text " Call hs_init_ghc() from your main() function to set these options.")
+
+ mkExtraObj dflags "c" (showSDoc dflags main)
+ where
+ main
+ | gopt Opt_NoHsMain dflags = Outputable.empty
+ | otherwise
+ = case ghcLink dflags of
+ LinkDynLib -> if platformOS (targetPlatform dflags) == OSMinGW32
+ then dllMain
+ else Outputable.empty
+ _ -> exeMain
+
+ exeMain = vcat [
+ text "#include \"Rts.h\"",
+ text "extern StgClosure ZCMain_main_closure;",
+ text "int main(int argc, char *argv[])",
+ char '{',
+ text " RtsConfig __conf = defaultRtsConfig;",
+ text " __conf.rts_opts_enabled = "
+ <> text (show (rtsOptsEnabled dflags)) <> semi,
+ text " __conf.rts_opts_suggestions = "
+ <> text (if rtsOptsSuggestions dflags
+ then "true"
+ else "false") <> semi,
+ case rtsOpts dflags of
+ Nothing -> Outputable.empty
+ Just opts -> text " __conf.rts_opts= " <>
+ text (show opts) <> semi,
+ text " __conf.rts_hs_main = true;",
+ text " return hs_main(argc,argv,&ZCMain_main_closure,__conf);",
+ char '}',
+ char '\n' -- final newline, to keep gcc happy
+ ]
+
+ dllMain = vcat [
+ text "#include \"Rts.h\"",
+ text "#include <windows.h>",
+ text "#include <stdbool.h>",
+ char '\n',
+ text "bool",
+ text "WINAPI",
+ text "DllMain ( HINSTANCE hInstance STG_UNUSED",
+ text " , DWORD reason STG_UNUSED",
+ text " , LPVOID reserved STG_UNUSED",
+ text " )",
+ text "{",
+ text " return true;",
+ text "}",
+ char '\n' -- final newline, to keep gcc happy
+ ]
+
+-- Write out the link info section into a new assembly file. Previously
+-- this was included as inline assembly in the main.c file but this
+-- is pretty fragile. gas gets upset trying to calculate relative offsets
+-- that span the .note section (notably .text) when debug info is present
+mkNoteObjsToLinkIntoBinary :: DynFlags -> [InstalledUnitId] -> IO [FilePath]
+mkNoteObjsToLinkIntoBinary dflags dep_packages = do
+ link_info <- getLinkInfo dflags dep_packages
+
+ if (platformSupportsSavingLinkOpts (platformOS (targetPlatform dflags)))
+ then fmap (:[]) $ mkExtraObj dflags "s" (showSDoc dflags (link_opts link_info))
+ else return []
+
+ where
+ link_opts info = hcat [
+ -- "link info" section (see Note [LinkInfo section])
+ makeElfNote ghcLinkInfoSectionName ghcLinkInfoNoteName 0 info,
+
+ -- ALL generated assembly must have this section to disable
+ -- executable stacks. See also
+ -- compiler/nativeGen/AsmCodeGen.hs for another instance
+ -- where we need to do this.
+ if platformHasGnuNonexecStack (targetPlatform dflags)
+ then text ".section .note.GNU-stack,\"\","
+ <> sectionType "progbits" <> char '\n'
+ else Outputable.empty
+ ]
+
+-- | Return the "link info" string
+--
+-- See Note [LinkInfo section]
+getLinkInfo :: DynFlags -> [InstalledUnitId] -> IO String
+getLinkInfo dflags dep_packages = do
+ package_link_opts <- getPackageLinkOpts dflags dep_packages
+ pkg_frameworks <- if platformUsesFrameworks (targetPlatform dflags)
+ then getPackageFrameworks dflags dep_packages
+ else return []
+ let extra_ld_inputs = ldInputs dflags
+ let
+ link_info = (package_link_opts,
+ pkg_frameworks,
+ rtsOpts dflags,
+ rtsOptsEnabled dflags,
+ gopt Opt_NoHsMain dflags,
+ map showOpt extra_ld_inputs,
+ getOpts dflags opt_l)
+ --
+ return (show link_info)
+
+platformSupportsSavingLinkOpts :: OS -> Bool
+platformSupportsSavingLinkOpts os
+ | os == OSSolaris2 = False -- see #5382
+ | otherwise = osElfTarget os
+
+-- See Note [LinkInfo section]
+ghcLinkInfoSectionName :: String
+ghcLinkInfoSectionName = ".debug-ghc-link-info"
+ -- if we use the ".debug" prefix, then strip will strip it by default
+
+-- Identifier for the note (see Note [LinkInfo section])
+ghcLinkInfoNoteName :: String
+ghcLinkInfoNoteName = "GHC link info"
+
+-- Returns 'False' if it was, and we can avoid linking, because the
+-- previous binary was linked with "the same options".
+checkLinkInfo :: DynFlags -> [InstalledUnitId] -> FilePath -> IO Bool
+checkLinkInfo dflags pkg_deps exe_file
+ | not (platformSupportsSavingLinkOpts (platformOS (targetPlatform dflags)))
+ -- ToDo: Windows and OS X do not use the ELF binary format, so
+ -- readelf does not work there. We need to find another way to do
+ -- this.
+ = return False -- conservatively we should return True, but not
+ -- linking in this case was the behaviour for a long
+ -- time so we leave it as-is.
+ | otherwise
+ = do
+ link_info <- getLinkInfo dflags pkg_deps
+ debugTraceMsg dflags 3 $ text ("Link info: " ++ link_info)
+ m_exe_link_info <- readElfNoteAsString dflags exe_file
+ ghcLinkInfoSectionName ghcLinkInfoNoteName
+ let sameLinkInfo = (Just link_info == m_exe_link_info)
+ debugTraceMsg dflags 3 $ case m_exe_link_info of
+ Nothing -> text "Exe link info: Not found"
+ Just s
+ | sameLinkInfo -> text ("Exe link info is the same")
+ | otherwise -> text ("Exe link info is different: " ++ s)
+ return (not sameLinkInfo)
+
+{- Note [LinkInfo section]
+ ~~~~~~~~~~~~~~~~~~~~~~~
+
+The "link info" is a string representing the parameters of the link. We save
+this information in the binary, and the next time we link, if nothing else has
+changed, we use the link info stored in the existing binary to decide whether
+to re-link or not.
+
+The "link info" string is stored in a ELF section called ".debug-ghc-link-info"
+(see ghcLinkInfoSectionName) with the SHT_NOTE type. For some time, it used to
+not follow the specified record-based format (see #11022).
+
+-}
+
+haveRtsOptsFlags :: DynFlags -> Bool
+haveRtsOptsFlags dflags =
+ isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of
+ RtsOptsSafeOnly -> False
+ _ -> True
diff --git a/compiler/main/SysTools/Info.hs b/compiler/main/SysTools/Info.hs
new file mode 100644
index 0000000000..e9dc68508b
--- /dev/null
+++ b/compiler/main/SysTools/Info.hs
@@ -0,0 +1,256 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+-----------------------------------------------------------------------------
+--
+-- Compiler information functions
+--
+-- (c) The GHC Team 2017
+--
+-----------------------------------------------------------------------------
+module SysTools.Info where
+
+import Exception
+import ErrUtils
+import DynFlags
+import Outputable
+import Util
+
+import Data.List
+import Data.IORef
+
+import System.IO
+
+import Platform
+import GhcPrelude
+
+import SysTools.Process
+
+{- Note [Run-time linker info]
+
+See also: Trac #5240, Trac #6063, Trac #10110
+
+Before 'runLink', we need to be sure to get the relevant information
+about the linker we're using at runtime to see if we need any extra
+options. For example, GNU ld requires '--reduce-memory-overheads' and
+'--hash-size=31' in order to use reasonable amounts of memory (see
+trac #5240.) But this isn't supported in GNU gold.
+
+Generally, the linker changing from what was detected at ./configure
+time has always been possible using -pgml, but on Linux it can happen
+'transparently' by installing packages like binutils-gold, which
+change what /usr/bin/ld actually points to.
+
+Clang vs GCC notes:
+
+For gcc, 'gcc -Wl,--version' gives a bunch of output about how to
+invoke the linker before the version information string. For 'clang',
+the version information for 'ld' is all that's output. For this
+reason, we typically need to slurp up all of the standard error output
+and look through it.
+
+Other notes:
+
+We cache the LinkerInfo inside DynFlags, since clients may link
+multiple times. The definition of LinkerInfo is there to avoid a
+circular dependency.
+
+-}
+
+{- Note [ELF needed shared libs]
+
+Some distributions change the link editor's default handling of
+ELF DT_NEEDED tags to include only those shared objects that are
+needed to resolve undefined symbols. For Template Haskell we need
+the last temporary shared library also if it is not needed for the
+currently linked temporary shared library. We specify --no-as-needed
+to override the default. This flag exists in GNU ld and GNU gold.
+
+The flag is only needed on ELF systems. On Windows (PE) and Mac OS X
+(Mach-O) the flag is not needed.
+
+-}
+
+{- Note [Windows static libGCC]
+
+The GCC versions being upgraded to in #10726 are configured with
+dynamic linking of libgcc supported. This results in libgcc being
+linked dynamically when a shared library is created.
+
+This introduces thus an extra dependency on GCC dll that was not
+needed before by shared libraries created with GHC. This is a particular
+issue on Windows because you get a non-obvious error due to this missing
+dependency. This dependent dll is also not commonly on your path.
+
+For this reason using the static libgcc is preferred as it preserves
+the same behaviour that existed before. There are however some very good
+reasons to have the shared version as well as described on page 181 of
+https://gcc.gnu.org/onlinedocs/gcc-5.2.0/gcc.pdf :
+
+"There are several situations in which an application should use the
+ shared ‘libgcc’ instead of the static version. The most common of these
+ is when the application wishes to throw and catch exceptions across different
+ shared libraries. In that case, each of the libraries as well as the application
+ itself should use the shared ‘libgcc’. "
+
+-}
+
+neededLinkArgs :: LinkerInfo -> [Option]
+neededLinkArgs (GnuLD o) = o
+neededLinkArgs (GnuGold o) = o
+neededLinkArgs (DarwinLD o) = o
+neededLinkArgs (SolarisLD o) = o
+neededLinkArgs (AixLD o) = o
+neededLinkArgs UnknownLD = []
+
+-- Grab linker info and cache it in DynFlags.
+getLinkerInfo :: DynFlags -> IO LinkerInfo
+getLinkerInfo dflags = do
+ info <- readIORef (rtldInfo dflags)
+ case info of
+ Just v -> return v
+ Nothing -> do
+ v <- getLinkerInfo' dflags
+ writeIORef (rtldInfo dflags) (Just v)
+ return v
+
+-- See Note [Run-time linker info].
+getLinkerInfo' :: DynFlags -> IO LinkerInfo
+getLinkerInfo' dflags = do
+ let platform = targetPlatform dflags
+ os = platformOS platform
+ (pgm,args0) = pgm_l dflags
+ args1 = map Option (getOpts dflags opt_l)
+ args2 = args0 ++ args1
+ args3 = filter notNull (map showOpt args2)
+
+ -- Try to grab the info from the process output.
+ parseLinkerInfo stdo _stde _exitc
+ | any ("GNU ld" `isPrefixOf`) stdo =
+ -- GNU ld specifically needs to use less memory. This especially
+ -- hurts on small object files. Trac #5240.
+ -- Set DT_NEEDED for all shared libraries. Trac #10110.
+ -- TODO: Investigate if these help or hurt when using split sections.
+ return (GnuLD $ map Option ["-Wl,--hash-size=31",
+ "-Wl,--reduce-memory-overheads",
+ -- ELF specific flag
+ -- see Note [ELF needed shared libs]
+ "-Wl,--no-as-needed"])
+
+ | any ("GNU gold" `isPrefixOf`) stdo =
+ -- GNU gold only needs --no-as-needed. Trac #10110.
+ -- ELF specific flag, see Note [ELF needed shared libs]
+ return (GnuGold [Option "-Wl,--no-as-needed"])
+
+ -- Unknown linker.
+ | otherwise = fail "invalid --version output, or linker is unsupported"
+
+ -- Process the executable call
+ info <- catchIO (do
+ case os of
+ OSSolaris2 ->
+ -- Solaris uses its own Solaris linker. Even all
+ -- GNU C are recommended to configure with Solaris
+ -- linker instead of using GNU binutils linker. Also
+ -- all GCC distributed with Solaris follows this rule
+ -- precisely so we assume here, the Solaris linker is
+ -- used.
+ return $ SolarisLD []
+ OSAIX ->
+ -- IBM AIX uses its own non-binutils linker as well
+ return $ AixLD []
+ OSDarwin ->
+ -- Darwin has neither GNU Gold or GNU LD, but a strange linker
+ -- that doesn't support --version. We can just assume that's
+ -- what we're using.
+ return $ DarwinLD []
+ OSMinGW32 ->
+ -- GHC doesn't support anything but GNU ld on Windows anyway.
+ -- Process creation is also fairly expensive on win32, so
+ -- we short-circuit here.
+ return $ GnuLD $ map Option
+ [ -- Reduce ld memory usage
+ "-Wl,--hash-size=31"
+ , "-Wl,--reduce-memory-overheads"
+ -- Emit gcc stack checks
+ -- Note [Windows stack usage]
+ , "-fstack-check"
+ -- Force static linking of libGCC
+ -- Note [Windows static libGCC]
+ , "-static-libgcc" ]
+ _ -> do
+ -- In practice, we use the compiler as the linker here. Pass
+ -- -Wl,--version to get linker version info.
+ (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm
+ (["-Wl,--version"] ++ args3)
+ c_locale_env
+ -- Split the output by lines to make certain kinds
+ -- of processing easier. In particular, 'clang' and 'gcc'
+ -- have slightly different outputs for '-Wl,--version', but
+ -- it's still easy to figure out.
+ parseLinkerInfo (lines stdo) (lines stde) exitc
+ )
+ (\err -> do
+ debugTraceMsg dflags 2
+ (text "Error (figuring out linker information):" <+>
+ text (show err))
+ errorMsg dflags $ hang (text "Warning:") 9 $
+ text "Couldn't figure out linker information!" $$
+ text "Make sure you're using GNU ld, GNU gold" <+>
+ text "or the built in OS X linker, etc."
+ return UnknownLD)
+ return info
+
+-- Grab compiler info and cache it in DynFlags.
+getCompilerInfo :: DynFlags -> IO CompilerInfo
+getCompilerInfo dflags = do
+ info <- readIORef (rtccInfo dflags)
+ case info of
+ Just v -> return v
+ Nothing -> do
+ v <- getCompilerInfo' dflags
+ writeIORef (rtccInfo dflags) (Just v)
+ return v
+
+-- See Note [Run-time linker info].
+getCompilerInfo' :: DynFlags -> IO CompilerInfo
+getCompilerInfo' dflags = do
+ let (pgm,_) = pgm_c dflags
+ -- Try to grab the info from the process output.
+ parseCompilerInfo _stdo stde _exitc
+ -- Regular GCC
+ | any ("gcc version" `isInfixOf`) stde =
+ return GCC
+ -- Regular clang
+ | any ("clang version" `isInfixOf`) stde =
+ return Clang
+ -- FreeBSD clang
+ | any ("FreeBSD clang version" `isInfixOf`) stde =
+ return Clang
+ -- XCode 5.1 clang
+ | any ("Apple LLVM version 5.1" `isPrefixOf`) stde =
+ return AppleClang51
+ -- XCode 5 clang
+ | any ("Apple LLVM version" `isPrefixOf`) stde =
+ return AppleClang
+ -- XCode 4.1 clang
+ | any ("Apple clang version" `isPrefixOf`) stde =
+ return AppleClang
+ -- Unknown linker.
+ | otherwise = fail "invalid -v output, or compiler is unsupported"
+
+ -- Process the executable call
+ info <- catchIO (do
+ (exitc, stdo, stde) <-
+ readProcessEnvWithExitCode pgm ["-v"] c_locale_env
+ -- Split the output by lines to make certain kinds
+ -- of processing easier.
+ parseCompilerInfo (lines stdo) (lines stde) exitc
+ )
+ (\err -> do
+ debugTraceMsg dflags 2
+ (text "Error (figuring out C compiler information):" <+>
+ text (show err))
+ errorMsg dflags $ hang (text "Warning:") 9 $
+ text "Couldn't figure out C compiler information!" $$
+ text "Make sure you're using GNU gcc, or clang"
+ return UnknownCC)
+ return info
diff --git a/compiler/main/SysTools/Process.hs b/compiler/main/SysTools/Process.hs
new file mode 100644
index 0000000000..cc8f67d139
--- /dev/null
+++ b/compiler/main/SysTools/Process.hs
@@ -0,0 +1,347 @@
+{-# LANGUAGE CPP #-}
+-----------------------------------------------------------------------------
+--
+-- Misc process handling code for SysTools
+--
+-- (c) The GHC Team 2017
+--
+-----------------------------------------------------------------------------
+module SysTools.Process where
+
+#include "HsVersions.h"
+
+import Exception
+import ErrUtils
+import DynFlags
+import FastString
+import Outputable
+import Panic
+import GhcPrelude
+import Util
+import SrcLoc ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan )
+
+import Control.Concurrent
+import Data.Char
+
+import System.Exit
+import System.Environment
+import System.FilePath
+import System.IO
+import System.IO.Error as IO
+import System.Process
+
+import FileCleanup
+
+-- Similar to System.Process.readCreateProcessWithExitCode, but stderr is
+-- inherited from the parent process, and output to stderr is not captured.
+readCreateProcessWithExitCode'
+ :: CreateProcess
+ -> IO (ExitCode, String) -- ^ stdout
+readCreateProcessWithExitCode' proc = do
+ (_, Just outh, _, pid) <-
+ createProcess proc{ std_out = CreatePipe }
+
+ -- fork off a thread to start consuming the output
+ output <- hGetContents outh
+ outMVar <- newEmptyMVar
+ _ <- forkIO $ evaluate (length output) >> putMVar outMVar ()
+
+ -- wait on the output
+ takeMVar outMVar
+ hClose outh
+
+ -- wait on the process
+ ex <- waitForProcess pid
+
+ return (ex, output)
+
+replaceVar :: (String, String) -> [(String, String)] -> [(String, String)]
+replaceVar (var, value) env =
+ (var, value) : filter (\(var',_) -> var /= var') env
+
+-- | Version of @System.Process.readProcessWithExitCode@ that takes a
+-- key-value tuple to insert into the environment.
+readProcessEnvWithExitCode
+ :: String -- ^ program path
+ -> [String] -- ^ program args
+ -> (String, String) -- ^ addition to the environment
+ -> IO (ExitCode, String, String) -- ^ (exit_code, stdout, stderr)
+readProcessEnvWithExitCode prog args env_update = do
+ current_env <- getEnvironment
+ readCreateProcessWithExitCode (proc prog args) {
+ env = Just (replaceVar env_update current_env) } ""
+
+-- Don't let gcc localize version info string, #8825
+c_locale_env :: (String, String)
+c_locale_env = ("LANGUAGE", "C")
+
+-- If the -B<dir> option is set, add <dir> to PATH. This works around
+-- a bug in gcc on Windows Vista where it can't find its auxiliary
+-- binaries (see bug #1110).
+getGccEnv :: [Option] -> IO (Maybe [(String,String)])
+getGccEnv opts =
+ if null b_dirs
+ then return Nothing
+ else do env <- getEnvironment
+ return (Just (map mangle_path env))
+ where
+ (b_dirs, _) = partitionWith get_b_opt opts
+
+ get_b_opt (Option ('-':'B':dir)) = Left dir
+ get_b_opt other = Right other
+
+ mangle_path (path,paths) | map toUpper path == "PATH"
+ = (path, '\"' : head b_dirs ++ "\";" ++ paths)
+ mangle_path other = other
+
+
+-----------------------------------------------------------------------------
+-- Running an external program
+
+runSomething :: DynFlags
+ -> String -- For -v message
+ -> String -- Command name (possibly a full path)
+ -- assumed already dos-ified
+ -> [Option] -- Arguments
+ -- runSomething will dos-ify them
+ -> IO ()
+
+runSomething dflags phase_name pgm args =
+ runSomethingFiltered dflags id phase_name pgm args Nothing Nothing
+
+-- | Run a command, placing the arguments in an external response file.
+--
+-- This command is used in order to avoid overlong command line arguments on
+-- Windows. The command line arguments are first written to an external,
+-- temporary response file, and then passed to the linker via @filepath.
+-- response files for passing them in. See:
+--
+-- https://gcc.gnu.org/wiki/Response_Files
+-- https://ghc.haskell.org/trac/ghc/ticket/10777
+runSomethingResponseFile
+ :: DynFlags -> (String->String) -> String -> String -> [Option]
+ -> Maybe [(String,String)] -> IO ()
+
+runSomethingResponseFile dflags filter_fn phase_name pgm args mb_env =
+ runSomethingWith dflags phase_name pgm args $ \real_args -> do
+ fp <- getResponseFile real_args
+ let args = ['@':fp]
+ r <- builderMainLoop dflags filter_fn pgm args Nothing mb_env
+ return (r,())
+ where
+ getResponseFile args = do
+ fp <- newTempName dflags TFL_CurrentModule "rsp"
+ withFile fp WriteMode $ \h -> do
+#if defined(mingw32_HOST_OS)
+ hSetEncoding h latin1
+#else
+ hSetEncoding h utf8
+#endif
+ hPutStr h $ unlines $ map escape args
+ return fp
+
+ -- Note: Response files have backslash-escaping, double quoting, and are
+ -- whitespace separated (some implementations use newline, others any
+ -- whitespace character). Therefore, escape any backslashes, newlines, and
+ -- double quotes in the argument, and surround the content with double
+ -- quotes.
+ --
+ -- Another possibility that could be considered would be to convert
+ -- backslashes in the argument to forward slashes. This would generally do
+ -- the right thing, since backslashes in general only appear in arguments
+ -- as part of file paths on Windows, and the forward slash is accepted for
+ -- those. However, escaping is more reliable, in case somehow a backslash
+ -- appears in a non-file.
+ escape x = concat
+ [ "\""
+ , concatMap
+ (\c ->
+ case c of
+ '\\' -> "\\\\"
+ '\n' -> "\\n"
+ '\"' -> "\\\""
+ _ -> [c])
+ x
+ , "\""
+ ]
+
+runSomethingFiltered
+ :: DynFlags -> (String->String) -> String -> String -> [Option]
+ -> Maybe FilePath -> Maybe [(String,String)] -> IO ()
+
+runSomethingFiltered dflags filter_fn phase_name pgm args mb_cwd mb_env = do
+ runSomethingWith dflags phase_name pgm args $ \real_args -> do
+ r <- builderMainLoop dflags filter_fn pgm real_args mb_cwd mb_env
+ return (r,())
+
+runSomethingWith
+ :: DynFlags -> String -> String -> [Option]
+ -> ([String] -> IO (ExitCode, a))
+ -> IO a
+
+runSomethingWith dflags phase_name pgm args io = do
+ let real_args = filter notNull (map showOpt args)
+ cmdLine = showCommandForUser pgm real_args
+ traceCmd dflags phase_name cmdLine $ handleProc pgm phase_name $ io real_args
+
+handleProc :: String -> String -> IO (ExitCode, r) -> IO r
+handleProc pgm phase_name proc = do
+ (rc, r) <- proc `catchIO` handler
+ case rc of
+ ExitSuccess{} -> return r
+ ExitFailure n -> throwGhcExceptionIO (
+ ProgramError ("`" ++ takeFileName pgm ++ "'" ++
+ " failed in phase `" ++ phase_name ++ "'." ++
+ " (Exit code: " ++ show n ++ ")"))
+ where
+ handler err =
+ if IO.isDoesNotExistError err
+ then does_not_exist
+ else throwGhcExceptionIO (ProgramError $ show err)
+
+ does_not_exist = throwGhcExceptionIO (InstallationError ("could not execute: " ++ pgm))
+
+
+builderMainLoop :: DynFlags -> (String -> String) -> FilePath
+ -> [String] -> Maybe FilePath -> Maybe [(String, String)]
+ -> IO ExitCode
+builderMainLoop dflags filter_fn pgm real_args mb_cwd mb_env = do
+ chan <- newChan
+
+ -- We use a mask here rather than a bracket because we want
+ -- to distinguish between cleaning up with and without an
+ -- exception. This is to avoid calling terminateProcess
+ -- unless an exception was raised.
+ let safely inner = mask $ \restore -> do
+ -- acquire
+ (hStdIn, hStdOut, hStdErr, hProcess) <- restore $
+ runInteractiveProcess pgm real_args mb_cwd mb_env
+ let cleanup_handles = do
+ hClose hStdIn
+ hClose hStdOut
+ hClose hStdErr
+ r <- try $ restore $ do
+ hSetBuffering hStdOut LineBuffering
+ hSetBuffering hStdErr LineBuffering
+ let make_reader_proc h = forkIO $ readerProc chan h filter_fn
+ bracketOnError (make_reader_proc hStdOut) killThread $ \_ ->
+ bracketOnError (make_reader_proc hStdErr) killThread $ \_ ->
+ inner hProcess
+ case r of
+ -- onException
+ Left (SomeException e) -> do
+ terminateProcess hProcess
+ cleanup_handles
+ throw e
+ -- cleanup when there was no exception
+ Right s -> do
+ cleanup_handles
+ return s
+ safely $ \h -> do
+ -- we don't want to finish until 2 streams have been complete
+ -- (stdout and stderr)
+ log_loop chan (2 :: Integer)
+ -- after that, we wait for the process to finish and return the exit code.
+ waitForProcess h
+ where
+ -- t starts at the number of streams we're listening to (2) decrements each
+ -- time a reader process sends EOF. We are safe from looping forever if a
+ -- reader thread dies, because they send EOF in a finally handler.
+ log_loop _ 0 = return ()
+ log_loop chan t = do
+ msg <- readChan chan
+ case msg of
+ BuildMsg msg -> do
+ putLogMsg dflags NoReason SevInfo noSrcSpan
+ (defaultUserStyle dflags) msg
+ log_loop chan t
+ BuildError loc msg -> do
+ putLogMsg dflags NoReason SevError (mkSrcSpan loc loc)
+ (defaultUserStyle dflags) msg
+ log_loop chan t
+ EOF ->
+ log_loop chan (t-1)
+
+readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO ()
+readerProc chan hdl filter_fn =
+ (do str <- hGetContents hdl
+ loop (linesPlatform (filter_fn str)) Nothing)
+ `finally`
+ writeChan chan EOF
+ -- ToDo: check errors more carefully
+ -- ToDo: in the future, the filter should be implemented as
+ -- a stream transformer.
+ where
+ loop [] Nothing = return ()
+ loop [] (Just err) = writeChan chan err
+ loop (l:ls) in_err =
+ case in_err of
+ Just err@(BuildError srcLoc msg)
+ | leading_whitespace l -> do
+ loop ls (Just (BuildError srcLoc (msg $$ text l)))
+ | otherwise -> do
+ writeChan chan err
+ checkError l ls
+ Nothing -> do
+ checkError l ls
+ _ -> panic "readerProc/loop"
+
+ checkError l ls
+ = case parseError l of
+ Nothing -> do
+ writeChan chan (BuildMsg (text l))
+ loop ls Nothing
+ Just (file, lineNum, colNum, msg) -> do
+ let srcLoc = mkSrcLoc (mkFastString file) lineNum colNum
+ loop ls (Just (BuildError srcLoc (text msg)))
+
+ leading_whitespace [] = False
+ leading_whitespace (x:_) = isSpace x
+
+parseError :: String -> Maybe (String, Int, Int, String)
+parseError s0 = case breakColon s0 of
+ Just (filename, s1) ->
+ case breakIntColon s1 of
+ Just (lineNum, s2) ->
+ case breakIntColon s2 of
+ Just (columnNum, s3) ->
+ Just (filename, lineNum, columnNum, s3)
+ Nothing ->
+ Just (filename, lineNum, 0, s2)
+ Nothing -> Nothing
+ Nothing -> Nothing
+
+breakColon :: String -> Maybe (String, String)
+breakColon xs = case break (':' ==) xs of
+ (ys, _:zs) -> Just (ys, zs)
+ _ -> Nothing
+
+breakIntColon :: String -> Maybe (Int, String)
+breakIntColon xs = case break (':' ==) xs of
+ (ys, _:zs)
+ | not (null ys) && all isAscii ys && all isDigit ys ->
+ Just (read ys, zs)
+ _ -> Nothing
+
+data BuildMessage
+ = BuildMsg !SDoc
+ | BuildError !SrcLoc !SDoc
+ | EOF
+
+-- Divvy up text stream into lines, taking platform dependent
+-- line termination into account.
+linesPlatform :: String -> [String]
+#if !defined(mingw32_HOST_OS)
+linesPlatform ls = lines ls
+#else
+linesPlatform "" = []
+linesPlatform xs =
+ case lineBreak xs of
+ (as,xs1) -> as : linesPlatform xs1
+ where
+ lineBreak "" = ("","")
+ lineBreak ('\r':'\n':xs) = ([],xs)
+ lineBreak ('\n':xs) = ([],xs)
+ lineBreak (x:xs) = let (as,bs) = lineBreak xs in (x:as,bs)
+
+#endif
diff --git a/compiler/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs
new file mode 100644
index 0000000000..82560af006
--- /dev/null
+++ b/compiler/main/SysTools/Tasks.hs
@@ -0,0 +1,343 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+-----------------------------------------------------------------------------
+--
+-- Tasks running external programs for SysTools
+--
+-- (c) The GHC Team 2017
+--
+-----------------------------------------------------------------------------
+module SysTools.Tasks where
+
+import Exception
+import ErrUtils
+import DynFlags
+import Outputable
+import Platform
+import Util
+
+import Data.Char
+import Data.List
+
+import System.IO
+import System.Process
+import GhcPrelude
+
+import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion)
+
+import SysTools.Process
+import SysTools.Info
+
+{-
+************************************************************************
+* *
+\subsection{Running an external program}
+* *
+************************************************************************
+-}
+
+runUnlit :: DynFlags -> [Option] -> IO ()
+runUnlit dflags args = do
+ let prog = pgm_L dflags
+ opts = getOpts dflags opt_L
+ runSomething dflags "Literate pre-processor" prog
+ (map Option opts ++ args)
+
+runCpp :: DynFlags -> [Option] -> IO ()
+runCpp dflags args = do
+ let (p,args0) = pgm_P dflags
+ args1 = map Option (getOpts dflags opt_P)
+ args2 = [Option "-Werror" | gopt Opt_WarnIsError dflags]
+ ++ [Option "-Wundef" | wopt Opt_WarnCPPUndef dflags]
+ mb_env <- getGccEnv args2
+ runSomethingFiltered dflags id "C pre-processor" p
+ (args0 ++ args1 ++ args2 ++ args) Nothing mb_env
+
+runPp :: DynFlags -> [Option] -> IO ()
+runPp dflags args = do
+ let prog = pgm_F dflags
+ opts = map Option (getOpts dflags opt_F)
+ runSomething dflags "Haskell pre-processor" prog (args ++ opts)
+
+runCc :: DynFlags -> [Option] -> IO ()
+runCc dflags args = do
+ let (p,args0) = pgm_c dflags
+ args1 = map Option (getOpts dflags opt_c)
+ args2 = args0 ++ args1 ++ args
+ mb_env <- getGccEnv args2
+ runSomethingResponseFile dflags cc_filter "C Compiler" p args2 mb_env
+ where
+ -- discard some harmless warnings from gcc that we can't turn off
+ cc_filter = unlines . doFilter . lines
+
+ {-
+ gcc gives warnings in chunks like so:
+ In file included from /foo/bar/baz.h:11,
+ from /foo/bar/baz2.h:22,
+ from wibble.c:33:
+ /foo/flibble:14: global register variable ...
+ /foo/flibble:15: warning: call-clobbered r...
+ We break it up into its chunks, remove any call-clobbered register
+ warnings from each chunk, and then delete any chunks that we have
+ emptied of warnings.
+ -}
+ doFilter = unChunkWarnings . filterWarnings . chunkWarnings []
+ -- We can't assume that the output will start with an "In file inc..."
+ -- line, so we start off expecting a list of warnings rather than a
+ -- location stack.
+ chunkWarnings :: [String] -- The location stack to use for the next
+ -- list of warnings
+ -> [String] -- The remaining lines to look at
+ -> [([String], [String])]
+ chunkWarnings loc_stack [] = [(loc_stack, [])]
+ chunkWarnings loc_stack xs
+ = case break loc_stack_start xs of
+ (warnings, lss:xs') ->
+ case span loc_start_continuation xs' of
+ (lsc, xs'') ->
+ (loc_stack, warnings) : chunkWarnings (lss : lsc) xs''
+ _ -> [(loc_stack, xs)]
+
+ filterWarnings :: [([String], [String])] -> [([String], [String])]
+ filterWarnings [] = []
+ -- If the warnings are already empty then we are probably doing
+ -- something wrong, so don't delete anything
+ filterWarnings ((xs, []) : zs) = (xs, []) : filterWarnings zs
+ filterWarnings ((xs, ys) : zs) = case filter wantedWarning ys of
+ [] -> filterWarnings zs
+ ys' -> (xs, ys') : filterWarnings zs
+
+ unChunkWarnings :: [([String], [String])] -> [String]
+ unChunkWarnings [] = []
+ unChunkWarnings ((xs, ys) : zs) = xs ++ ys ++ unChunkWarnings zs
+
+ loc_stack_start s = "In file included from " `isPrefixOf` s
+ loc_start_continuation s = " from " `isPrefixOf` s
+ wantedWarning w
+ | "warning: call-clobbered register used" `isContainedIn` w = False
+ | otherwise = True
+
+isContainedIn :: String -> String -> Bool
+xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
+
+-- | Run the linker with some arguments and return the output
+askLd :: DynFlags -> [Option] -> IO String
+askLd dflags args = do
+ let (p,args0) = pgm_l dflags
+ args1 = map Option (getOpts dflags opt_l)
+ args2 = args0 ++ args1 ++ args
+ mb_env <- getGccEnv args2
+ runSomethingWith dflags "gcc" p args2 $ \real_args ->
+ readCreateProcessWithExitCode' (proc p real_args){ env = mb_env }
+
+runSplit :: DynFlags -> [Option] -> IO ()
+runSplit dflags args = do
+ let (p,args0) = pgm_s dflags
+ runSomething dflags "Splitter" p (args0++args)
+
+runAs :: DynFlags -> [Option] -> IO ()
+runAs dflags args = do
+ let (p,args0) = pgm_a dflags
+ args1 = map Option (getOpts dflags opt_a)
+ args2 = args0 ++ args1 ++ args
+ mb_env <- getGccEnv args2
+ runSomethingFiltered dflags id "Assembler" p args2 Nothing mb_env
+
+-- | Run the LLVM Optimiser
+runLlvmOpt :: DynFlags -> [Option] -> IO ()
+runLlvmOpt dflags args = do
+ let (p,args0) = pgm_lo dflags
+ args1 = map Option (getOpts dflags opt_lo)
+ runSomething dflags "LLVM Optimiser" p (args0 ++ args1 ++ args)
+
+-- | Run the LLVM Compiler
+runLlvmLlc :: DynFlags -> [Option] -> IO ()
+runLlvmLlc dflags args = do
+ let (p,args0) = pgm_lc dflags
+ args1 = map Option (getOpts dflags opt_lc)
+ runSomething dflags "LLVM Compiler" p (args0 ++ args1 ++ args)
+
+-- | Run the clang compiler (used as an assembler for the LLVM
+-- backend on OS X as LLVM doesn't support the OS X system
+-- assembler)
+runClang :: DynFlags -> [Option] -> IO ()
+runClang dflags args = do
+ let (clang,_) = pgm_lcc dflags
+ -- be careful what options we call clang with
+ -- see #5903 and #7617 for bugs caused by this.
+ (_,args0) = pgm_a dflags
+ args1 = map Option (getOpts dflags opt_a)
+ args2 = args0 ++ args1 ++ args
+ mb_env <- getGccEnv args2
+ Exception.catch (do
+ runSomethingFiltered dflags id "Clang (Assembler)" clang args2 Nothing mb_env
+ )
+ (\(err :: SomeException) -> do
+ errorMsg dflags $
+ text ("Error running clang! you need clang installed to use the" ++
+ " LLVM backend") $+$
+ text "(or GHC tried to execute clang incorrectly)"
+ throwIO err
+ )
+
+-- | Figure out which version of LLVM we are running this session
+figureLlvmVersion :: DynFlags -> IO (Maybe (Int, Int))
+figureLlvmVersion dflags = do
+ let (pgm,opts) = pgm_lc dflags
+ args = filter notNull (map showOpt opts)
+ -- we grab the args even though they should be useless just in
+ -- case the user is using a customised 'llc' that requires some
+ -- of the options they've specified. llc doesn't care what other
+ -- options are specified when '-version' is used.
+ args' = args ++ ["-version"]
+ ver <- catchIO (do
+ (pin, pout, perr, _) <- runInteractiveProcess pgm args'
+ Nothing Nothing
+ {- > llc -version
+ LLVM (http://llvm.org/):
+ LLVM version 3.5.2
+ ...
+ -}
+ hSetBinaryMode pout False
+ _ <- hGetLine pout
+ vline <- dropWhile (not . isDigit) `fmap` hGetLine pout
+ v <- case span (/= '.') vline of
+ ("",_) -> fail "no digits!"
+ (x,y) -> return (read x
+ , read $ takeWhile isDigit $ drop 1 y)
+
+ hClose pin
+ hClose pout
+ hClose perr
+ return $ Just v
+ )
+ (\err -> do
+ debugTraceMsg dflags 2
+ (text "Error (figuring out LLVM version):" <+>
+ text (show err))
+ errorMsg dflags $ vcat
+ [ text "Warning:", nest 9 $
+ text "Couldn't figure out LLVM version!" $$
+ text ("Make sure you have installed LLVM " ++
+ llvmVersionStr supportedLlvmVersion) ]
+ return Nothing)
+ return ver
+
+
+runLink :: DynFlags -> [Option] -> IO ()
+runLink dflags args = do
+ -- See Note [Run-time linker info]
+ linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags
+ let (p,args0) = pgm_l dflags
+ args1 = map Option (getOpts dflags opt_l)
+ args2 = args0 ++ linkargs ++ args1 ++ args
+ mb_env <- getGccEnv args2
+ runSomethingResponseFile 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
+ symbols 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
+ choose 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 the 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 the 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
+ linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags
+ let args1 = map Option (getOpts dflags opt_l)
+ args2 = [Option "-static"] ++ args1 ++ args ++ linkargs
+ libtool = pgm_libtool dflags
+ mb_env <- getGccEnv args2
+ runSomethingFiltered dflags id "Linker" libtool args2 Nothing mb_env
+
+runAr :: DynFlags -> Maybe FilePath -> [Option] -> IO ()
+runAr dflags cwd args = do
+ let ar = pgm_ar dflags
+ runSomethingFiltered dflags id "Ar" ar args cwd Nothing
+
+askAr :: DynFlags -> Maybe FilePath -> [Option] -> IO String
+askAr dflags mb_cwd args = do
+ let ar = pgm_ar dflags
+ runSomethingWith dflags "Ar" ar args $ \real_args ->
+ readCreateProcessWithExitCode' (proc ar real_args){ cwd = mb_cwd }
+
+runRanlib :: DynFlags -> [Option] -> IO ()
+runRanlib dflags args = do
+ let ranlib = pgm_ranlib dflags
+ runSomethingFiltered dflags id "Ranlib" ranlib args Nothing Nothing
+
+runMkDLL :: DynFlags -> [Option] -> IO ()
+runMkDLL dflags args = do
+ let (p,args0) = pgm_dll dflags
+ args1 = args0 ++ args
+ mb_env <- getGccEnv (args0++args)
+ runSomethingFiltered dflags id "Make DLL" p args1 Nothing mb_env
+
+runWindres :: DynFlags -> [Option] -> IO ()
+runWindres dflags args = do
+ let (gcc, gcc_args) = pgm_c dflags
+ windres = pgm_windres dflags
+ opts = map Option (getOpts dflags opt_windres)
+ quote x = "\"" ++ x ++ "\""
+ args' = -- If windres.exe and gcc.exe are in a directory containing
+ -- spaces then windres fails to run gcc. We therefore need
+ -- to tell it what command to use...
+ Option ("--preprocessor=" ++
+ unwords (map quote (gcc :
+ map showOpt gcc_args ++
+ map showOpt opts ++
+ ["-E", "-xc", "-DRC_INVOKED"])))
+ -- ...but if we do that then if windres calls popen then
+ -- it can't understand the quoting, so we have to use
+ -- --use-temp-file so that it interprets it correctly.
+ -- See #1828.
+ : Option "--use-temp-file"
+ : args
+ mb_env <- getGccEnv gcc_args
+ runSomethingFiltered dflags id "Windres" windres args' Nothing mb_env
+
+touch :: DynFlags -> String -> String -> IO ()
+touch dflags purpose arg =
+ runSomething dflags purpose (pgm_T dflags) [FileOption "" arg]