X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FSysTools.lhs;h=5c434d0db3767d40e9b6aa5aa16d6348fd12c33c;hp=9710bcb96cd28afa349f52bec55bd23799b737a0;hb=98344985c816d0abe17192f38b1663d85d8d2f9b;hpb=d1c1b7d0e7b94ede238845c91f58582bad3b3ef3 diff --git a/ghc/compiler/main/SysTools.lhs b/ghc/compiler/main/SysTools.lhs index 9710bcb..5c434d0 100644 --- a/ghc/compiler/main/SysTools.lhs +++ b/ghc/compiler/main/SysTools.lhs @@ -47,20 +47,24 @@ module SysTools ( import DriverPhases ( isHaskellUserSrcFilename ) import Config import Outputable +import ErrUtils ( putMsg, debugTraceMsg, showPass, Severity(..), Messages ) import Panic ( GhcException(..) ) -import Util ( Suffix, global, notNull, consIORef ) -import DynFlags ( DynFlags(..), DynFlag(..), dopt, Option(..) ) +import Util ( Suffix, global, notNull, consIORef, joinFileName, + normalisePath, pgmPath, platformPath, joinFileExt ) +import DynFlags ( DynFlags(..), DynFlag(..), dopt, Option(..), + setTmpDir, defaultDynFlags ) -import EXCEPTION ( throwDyn ) +import EXCEPTION ( throwDyn, finally ) import DATA_IOREF ( IORef, readIORef, writeIORef ) import DATA_INT import Monad ( when, unless ) import System ( ExitCode(..), getEnv, system ) -import IO ( try, catch, - openFile, hPutStrLn, hPutStr, hClose, hFlush, IOMode(..), - stderr ) +import IO ( try, catch, hGetContents, + openFile, hPutStr, hClose, hFlush, IOMode(..), + stderr, ioError, isDoesNotExistError ) import Directory ( doesFileExist, removeFile ) +import Maybe ( isJust ) import List ( partition ) -- GHC <= 4.08 didn't have rawSystem, and runs into problems with long command @@ -85,8 +89,16 @@ import CString ( CString, peekCString ) #if __GLASGOW_HASKELL__ < 603 -- rawSystem comes from libghccompat.a in stage1 import Compat.RawSystem ( rawSystem ) +import GHC.IOBase ( IOErrorType(..) ) +import System.IO.Error ( ioeGetErrorType ) #else -import System.Cmd ( rawSystem ) +import System.Process ( runInteractiveProcess, getProcessExitCode ) +import System.IO ( hSetBuffering, hGetLine, BufferMode(..) ) +import Control.Concurrent( forkIO, newChan, readChan, writeChan ) +import Text.Regex +import Data.Char ( isSpace ) +import FastString ( mkFastString ) +import SrcLoc ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan ) #endif \end{code} @@ -187,7 +199,7 @@ getTopDir = readIORef v_TopDir %************************************************************************ \begin{code} -initSysTools :: [String] -- Command-line arguments starting "-B" +initSysTools :: Maybe String -- Maybe TopDir path (without the '-B' prefix) -> DynFlags -> IO DynFlags -- Set all the mutable variables above, holding @@ -196,8 +208,8 @@ initSysTools :: [String] -- Command-line arguments starting "-B" -- (c) the GHC usage message -initSysTools minusB_args dflags - = do { (am_installed, top_dir) <- findTopDir minusB_args +initSysTools mbMinusB dflags + = do { (am_installed, top_dir) <- findTopDir mbMinusB ; writeIORef v_TopDir top_dir -- top_dir -- for "installed" this is the root of GHC's support files @@ -207,8 +219,8 @@ initSysTools minusB_args dflags ; let installed, installed_bin :: FilePath -> FilePath installed_bin pgm = pgmPath top_dir pgm installed file = pgmPath top_dir file - inplace dir pgm = pgmPath (top_dir `slash` - cPROJECT_DIR `slash` dir) pgm + inplace dir pgm = pgmPath (top_dir `joinFileName` + cPROJECT_DIR `joinFileName` dir) pgm ; let pkgconfig_path | am_installed = installed "package.conf" @@ -237,32 +249,32 @@ initSysTools minusB_args dflags | am_installed = installed_bin cGHC_MANGLER_PGM | otherwise = inplace cGHC_MANGLER_DIR_REL cGHC_MANGLER_PGM + ; let dflags0 = defaultDynFlags #ifndef mingw32_HOST_OS -- check whether TMPDIR is set in the environment - ; IO.try (do dir <- getEnv "TMPDIR" -- fails if not set - setTmpDir dir - return () - ) + ; e_tmpdir <- IO.try (getEnv "TMPDIR") -- fails if not set #else -- On Win32, consult GetTempPath() for a temp dir. -- => it first tries TMP, TEMP, then finally the -- Windows directory(!). The directory is in short-path -- form. - ; IO.try (do + ; e_tmpdir <- + IO.try (do let len = (2048::Int) buf <- mallocArray len ret <- getTempPath len buf - tdir <- - if ret == 0 then do + if ret == 0 then do -- failed, consult TMPDIR. free buf getEnv "TMPDIR" - else do + else do s <- peekCString buf free buf - return s - setTmpDir tdir) + return s) #endif + ; let dflags1 = case e_tmpdir of + Left _ -> dflags0 + Right d -> setTmpDir d dflags0 -- Check that the package config exists ; config_exists <- doesFileExist pkgconfig_path @@ -364,7 +376,7 @@ initSysTools minusB_args dflags ; writeIORef v_Pgm_T touch_path ; writeIORef v_Pgm_CP cp_path - ; return dflags{ + ; return dflags1{ pgm_L = unlit_path, pgm_P = cpp_path, pgm_F = "", @@ -388,9 +400,8 @@ foreign import stdcall unsafe "GetTempPathA" getTempPath :: Int -> CString -> IO -- -- Plan of action: -- 1. Set proto_top_dir --- a) look for (the last) -B flag, and use it --- b) if there are no -B flags, get the directory --- where GHC is running (only on Windows) +-- if there is no given TopDir path, get the directory +-- where GHC is running (only on Windows) -- -- 2. If package.conf exists in proto_top_dir, we are running -- installed; and TopDir = proto_top_dir @@ -401,29 +412,28 @@ foreign import stdcall unsafe "GetTempPathA" getTempPath :: Int -> CString -> IO -- -- This is very gruesome indeed -findTopDir :: [String] - -> IO (Bool, -- True <=> am installed, False <=> in-place - String) -- TopDir (in Unix format '/' separated) +findTopDir :: Maybe String -- Maybe TopDir path (without the '-B' prefix). + -> IO (Bool, -- True <=> am installed, False <=> in-place + String) -- TopDir (in Unix format '/' separated) -findTopDir minusbs +findTopDir mbMinusB = do { top_dir <- get_proto -- Discover whether we're running in a build tree or in an installation, -- by looking for the package configuration file. - ; am_installed <- doesFileExist (top_dir `slash` "package.conf") + ; am_installed <- doesFileExist (top_dir `joinFileName` "package.conf") ; return (am_installed, top_dir) } where -- get_proto returns a Unix-format path (relying on getBaseDir to do so too) - get_proto | notNull minusbs - = return (normalisePath (drop 2 (last minusbs))) -- 2 for "-B" - | otherwise - = do { maybe_exec_dir <- getBaseDir -- Get directory of executable - ; case maybe_exec_dir of -- (only works on Windows; - -- returns Nothing on Unix) - Nothing -> throwDyn (InstallationError "missing -B option") - Just dir -> return dir - } + get_proto = case mbMinusB of + Just minusb -> return (normalisePath minusb) + Nothing + -> do maybe_exec_dir <- getBaseDir -- Get directory of executable + case maybe_exec_dir of -- (only works on Windows; + -- returns Nothing on Unix) + Nothing -> throwDyn (InstallationError "missing -B option") + Just dir -> return dir \end{code} @@ -453,7 +463,21 @@ runPp dflags args = do runCc :: DynFlags -> [Option] -> IO () runCc dflags args = do let (p,args0) = pgm_c dflags - runSomething dflags "C Compiler" p (args0++args) + runSomethingFiltered dflags cc_filter "C Compiler" p (args0++args) + where + -- discard some harmless warnings from gcc that we can't turn off + cc_filter str = unlines (do_filter (lines str)) + + do_filter [] = [] + do_filter ls@(l:ls') + | (w:rest) <- dropWhile (isJust .matchRegex r_from) ls, + isJust (matchRegex r_warn w) + = do_filter rest + | otherwise + = l : do_filter ls' + + r_from = mkRegex "from.*:[0-9]+" + r_warn = mkRegex "warning: call-clobbered register used" runMangle :: DynFlags -> [Option] -> IO () runMangle dflags args = do @@ -487,7 +511,7 @@ touch dflags purpose arg = do copy :: DynFlags -> String -> String -> String -> IO () copy dflags purpose from to = do - when (verbosity dflags >= 2) $ hPutStrLn stderr ("*** " ++ purpose) + showPass dflags purpose h <- openFile to WriteMode ls <- readFile from -- inefficient, but it'll do for now. @@ -518,42 +542,9 @@ getUsageMsgPaths = readIORef v_Path_usages \begin{code} GLOBAL_VAR(v_FilesToClean, [], [String] ) -GLOBAL_VAR(v_TmpDir, cDEFAULT_TMPDIR, String ) - -- v_TmpDir has no closing '/' \end{code} \begin{code} -setTmpDir dir = writeIORef v_TmpDir (canonicalise dir) - where -#if !defined(mingw32_HOST_OS) - canonicalise p = normalisePath p -#else - -- Canonicalisation of temp path under win32 is a bit more - -- involved: (a) strip trailing slash, - -- (b) normalise slashes - -- (c) just in case, if there is a prefix /cygdrive/x/, change to x: - -- - canonicalise path = normalisePath (xltCygdrive (removeTrailingSlash path)) - - -- if we're operating under cygwin, and TMP/TEMP is of - -- the form "/cygdrive/drive/path", translate this to - -- "drive:/path" (as GHC isn't a cygwin app and doesn't - -- understand /cygdrive paths.) - xltCygdrive path - | "/cygdrive/" `isPrefixOf` path = - case drop (length "/cygdrive/") path of - drive:xs@('/':_) -> drive:':':xs - _ -> path - | otherwise = path - - -- strip the trailing backslash (awful, but we only do this once). - removeTrailingSlash path = - case last path of - '/' -> init path - '\\' -> init path - _ -> path -#endif - cleanTempFiles :: DynFlags -> IO () cleanTempFiles dflags = do fs <- readIORef v_FilesToClean @@ -569,16 +560,15 @@ cleanTempFilesExcept dflags dont_delete -- find a temporary name that doesn't already exist. -newTempName :: Suffix -> IO FilePath -newTempName extn +newTempName :: DynFlags -> Suffix -> IO FilePath +newTempName DynFlags{tmpDir=tmp_dir} extn = do x <- getProcessID - tmp_dir <- readIORef v_TmpDir - findTempName tmp_dir x + findTempName (tmp_dir ++ "/ghc" ++ show x ++ "_") 0 where - findTempName tmp_dir x - = do let filename = tmp_dir ++ "/ghc" ++ show x ++ '.':extn + findTempName prefix x + = do let filename = (prefix ++ show x) `joinFileExt` extn b <- doesFileExist filename - if b then findTempName tmp_dir (x+1) + if b then findTempName prefix (x+1) else do consIORef v_FilesToClean filename -- clean it up later return filename @@ -593,8 +583,6 @@ removeTmpFiles dflags fs ("Deleting: " ++ unwords deletees) (mapM_ rm deletees) where - verb = verbosity dflags - -- Flat out refuse to delete files that are likely to be source input -- files (is there a worse bug than having a compiler delete your source -- files?) @@ -604,15 +592,14 @@ removeTmpFiles dflags fs warnNon act | null non_deletees = act | otherwise = do - hPutStrLn stderr ("WARNING - NOT deleting source files: " ++ unwords non_deletees) + putMsg dflags (text "WARNING - NOT deleting source files:" <+> hsep (map text non_deletees)) act (non_deletees, deletees) = partition isHaskellUserSrcFilename fs rm f = removeFile f `IO.catch` (\_ignored -> - when (verb >= 2) $ - hPutStrLn stderr ("Warning: deleting non-existent " ++ f) + debugTraceMsg dflags 2 (ptext SLIT("Warning: deleting non-existent") <+> text f) ) @@ -627,22 +614,139 @@ runSomething :: DynFlags -- runSomething will dos-ify them -> IO () -runSomething dflags phase_name pgm args = do +runSomething dflags phase_name pgm args = + runSomethingFiltered dflags id phase_name pgm args + +runSomethingFiltered + :: DynFlags -> (String->String) -> String -> String -> [Option] -> IO () + +runSomethingFiltered dflags filter_fn phase_name pgm args = do let real_args = filter notNull (map showOpt args) traceCmd dflags phase_name (unwords (pgm:real_args)) $ do - exit_code <- rawSystem pgm real_args - case exit_code of - ExitSuccess -> - return () - -- rawSystem returns (ExitFailure 127) if the exec failed for any - -- reason (eg. the program doesn't exist). This is the only clue - -- we have, but we need to report something to the user because in - -- the case of a missing program there will otherwise be no output - -- at all. - ExitFailure 127 -> - throwDyn (InstallationError ("could not execute: " ++ pgm)) - ExitFailure _other -> - throwDyn (PhaseFailed phase_name exit_code) + (exit_code, doesn'tExist) <- + IO.catch (do + rc <- builderMainLoop dflags filter_fn pgm real_args + case rc of + ExitSuccess{} -> return (rc, False) + ExitFailure n + -- rawSystem returns (ExitFailure 127) if the exec failed for any + -- reason (eg. the program doesn't exist). This is the only clue + -- we have, but we need to report something to the user because in + -- the case of a missing program there will otherwise be no output + -- at all. + | n == 127 -> return (rc, True) + | otherwise -> return (rc, False)) + -- Should 'rawSystem' generate an IO exception indicating that + -- 'pgm' couldn't be run rather than a funky return code, catch + -- this here (the win32 version does this, but it doesn't hurt + -- to test for this in general.) + (\ err -> + if IO.isDoesNotExistError err +#if defined(mingw32_HOST_OS) && __GLASGOW_HASKELL__ < 604 + -- the 'compat' version of rawSystem under mingw32 always + -- maps 'errno' to EINVAL to failure. + || case (ioeGetErrorType err ) of { InvalidArgument{} -> True ; _ -> False} +#endif + then return (ExitFailure 1, True) + else IO.ioError err) + case (doesn'tExist, exit_code) of + (True, _) -> throwDyn (InstallationError ("could not execute: " ++ pgm)) + (_, ExitSuccess) -> return () + _ -> throwDyn (PhaseFailed phase_name exit_code) + + + +#if __GLASGOW_HASKELL__ < 603 +builderMainLoop dflags filter_fn pgm real_args = do + rawSystem pgm real_args +#else +builderMainLoop dflags filter_fn pgm real_args = do + chan <- newChan + (hStdIn, hStdOut, hStdErr, hProcess) <- runInteractiveProcess pgm real_args Nothing Nothing + + -- and run a loop piping the output from the compiler to the log_action in DynFlags + hSetBuffering hStdOut LineBuffering + hSetBuffering hStdErr LineBuffering + forkIO (readerProc chan hStdOut filter_fn) + forkIO (readerProc chan hStdErr filter_fn) + rc <- loop chan hProcess 2 1 ExitSuccess + hClose hStdIn + hClose hStdOut + hClose hStdErr + return rc + where + -- status starts at zero, and increments each time either + -- a reader process gets EOF, or the build proc exits. We wait + -- for all of these to happen (status==3). + -- ToDo: we should really have a contingency plan in case any of + -- the threads dies, such as a timeout. + loop chan hProcess 0 0 exitcode = return exitcode + loop chan hProcess t p exitcode = do + mb_code <- if p > 0 + then getProcessExitCode hProcess + else return Nothing + case mb_code of + Just code -> loop chan hProcess t (p-1) code + Nothing + | t > 0 -> do + msg <- readChan chan + case msg of + BuildMsg msg -> do + log_action dflags SevInfo noSrcSpan defaultUserStyle msg + loop chan hProcess t p exitcode + BuildError loc msg -> do + log_action dflags SevError (mkSrcSpan loc loc) defaultUserStyle msg + loop chan hProcess t p exitcode + EOF -> + loop chan hProcess (t-1) p exitcode + | otherwise -> loop chan hProcess t p exitcode + +readerProc chan hdl filter_fn = + (do str <- hGetContents hdl + loop (lines (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 + + checkError l ls + = case matchRegex errRegex l of + Nothing -> do + writeChan chan (BuildMsg (text l)) + loop ls Nothing + Just (file':lineno':colno':msg:_) -> do + let file = mkFastString file' + lineno = read lineno'::Int + colno = case colno' of + "" -> 0 + _ -> read (init colno') :: Int + srcLoc = mkSrcLoc file lineno colno + loop ls (Just (BuildError srcLoc (text msg))) + + leading_whitespace [] = False + leading_whitespace (x:_) = isSpace x + +errRegex = mkRegex "^([^:]*):([0-9]+):([0-9]+:)?(.*)" + +data BuildMessage + = BuildMsg !SDoc + | BuildError !SrcLoc !SDoc + | EOF +#endif showOpt (FileOption pre f) = pre ++ platformPath f showOpt (Option "") = "" @@ -653,8 +757,8 @@ traceCmd :: DynFlags -> String -> String -> IO () -> IO () -- b) don't do it at all if dry-run is set traceCmd dflags phase_name cmd_line action = do { let verb = verbosity dflags - ; when (verb >= 2) $ hPutStrLn stderr ("*** " ++ phase_name) - ; when (verb >= 3) $ hPutStrLn stderr cmd_line + ; showPass dflags phase_name + ; debugTraceMsg dflags 3 (text cmd_line) ; hFlush stderr -- Test for -n flag @@ -664,68 +768,11 @@ traceCmd dflags phase_name cmd_line action ; action `IO.catch` handle_exn verb }} where - handle_exn verb exn = do { when (verb >= 2) (hPutStr stderr "\n") - ; when (verb >= 3) (hPutStrLn stderr ("Failed: " ++ cmd_line ++ (show exn))) + handle_exn verb exn = do { debugTraceMsg dflags 2 (char '\n') + ; debugTraceMsg dflags 2 (ptext SLIT("Failed:") <+> text cmd_line <+> text (show exn)) ; throwDyn (PhaseFailed phase_name (ExitFailure 1)) } \end{code} - -%************************************************************************ -%* * -\subsection{Path names} -%* * -%************************************************************************ - -We maintain path names in Unix form ('/'-separated) right until -the last moment. On Windows we dos-ify them just before passing them -to the Windows command. - -The alternative, of using '/' consistently on Unix and '\' on Windows, -proved quite awkward. There were a lot more calls to platformPath, -and even on Windows we might invoke a unix-like utility (eg 'sh'), which -interpreted a command line 'foo\baz' as 'foobaz'. - -\begin{code} ------------------------------------------------------------------------------ --- Convert filepath into platform / MSDOS form. - -normalisePath :: String -> String --- Just changes '\' to '/' - -pgmPath :: String -- Directory string in Unix format - -> String -- Program name with no directory separators - -- (e.g. copy /y) - -> String -- Program invocation string in native format - - - -#if defined(mingw32_HOST_OS) ---------------------- Windows version ------------------ -normalisePath xs = subst '\\' '/' xs -platformPath p = subst '/' '\\' p -pgmPath dir pgm = platformPath dir ++ '\\' : pgm - -subst a b ls = map (\ x -> if x == a then b else x) ls -#else ---------------------- Non-Windows version -------------- -normalisePath xs = xs -pgmPath dir pgm = dir ++ '/' : pgm -platformPath stuff = stuff --------------------------------------------------------- -#endif - -\end{code} - - ------------------------------------------------------------------------------ - Path name construction - -\begin{code} -slash :: String -> String -> String -slash s1 s2 = s1 ++ ('/' : s2) -\end{code} - - %************************************************************************ %* * \subsection{Support code} @@ -736,8 +783,8 @@ slash s1 s2 = s1 ++ ('/' : s2) ----------------------------------------------------------------------------- -- Define getBaseDir :: IO (Maybe String) -#if defined(mingw32_HOST_OS) getBaseDir :: IO (Maybe String) +#if defined(mingw32_HOST_OS) -- Assuming we are running ghc, accessed by path $()/bin/ghc.exe, -- return the path $(stuff). Note that we drop the "bin/" directory too. getBaseDir = do let len = (2048::Int) -- plenty, PATH_MAX is 512 under Win32. @@ -753,7 +800,7 @@ getBaseDir = do let len = (2048::Int) -- plenty, PATH_MAX is 512 under Win32. foreign import stdcall unsafe "GetModuleFileNameA" getModuleFileName :: Ptr () -> CString -> Int -> IO Int32 #else -getBaseDir :: IO (Maybe String) = do return Nothing +getBaseDir = return Nothing #endif #ifdef mingw32_HOST_OS