3eb574438e46bd48892ecdd863bbe7925cacf433
[ghc-hetmet.git] / compiler / main / SysTools.lhs
1 -----------------------------------------------------------------------------
2 --
3 -- (c) The University of Glasgow 2001-2003
4 --
5 -- Access to system tools: gcc, cp, rm etc
6 --
7 -----------------------------------------------------------------------------
8
9 \begin{code}
10 module SysTools (
11         -- Initialisation
12         initSysTools,
13
14         -- Interface to system tools
15         runUnlit, runCpp, runCc, -- [Option] -> IO ()
16         runPp,                   -- [Option] -> IO ()
17         runSplit,                -- [Option] -> IO ()
18         runAs, runLink,          -- [Option] -> IO ()
19         runMkDLL,
20         runWindres,
21         runLlvmOpt,
22         runLlvmLlc,
23
24         touch,                  -- String -> String -> IO ()
25         copy,
26         copyWithHeader,
27         getExtraViaCOpts,
28
29         -- Temporary-file management
30         setTmpDir,
31         newTempName,
32         cleanTempDirs, cleanTempFiles, cleanTempFilesExcept,
33         addFilesToClean,
34
35         Option(..)
36
37  ) where
38
39 #include "HsVersions.h"
40
41 import DriverPhases
42 import Config
43 import Outputable
44 import ErrUtils
45 import Panic
46 import Util
47 import DynFlags
48 import Exception
49
50 import Data.IORef
51 import Control.Monad
52 import System.Exit
53 import System.Environment
54 import System.FilePath
55 import System.IO
56 import System.IO.Error as IO
57 import System.Directory
58 import Data.Char
59 import Data.List
60 import qualified Data.Map as Map
61
62 #ifndef mingw32_HOST_OS
63 import qualified System.Posix.Internals
64 #else /* Must be Win32 */
65 import Foreign
66 import Foreign.C.String
67 #endif
68
69 import System.Process
70 import Control.Concurrent
71 import FastString
72 import SrcLoc           ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan )
73 \end{code}
74
75 How GHC finds its files
76 ~~~~~~~~~~~~~~~~~~~~~~~
77
78 [Note topdir]
79
80 GHC needs various support files (library packages, RTS etc), plus
81 various auxiliary programs (cp, gcc, etc).  It starts by finding topdir,
82 the root of GHC's support files
83
84 On Unix:
85   - ghc always has a shell wrapper that passes a -B<dir> option
86
87 On Windows:
88   - ghc never has a shell wrapper.
89   - we can find the location of the ghc binary, which is
90         $topdir/bin/<something>.exe
91     where <something> may be "ghc", "ghc-stage2", or similar
92   - we strip off the "bin/<something>.exe" to leave $topdir.
93
94 from topdir we can find package.conf, ghc-asm, etc.
95
96
97 SysTools.initSysProgs figures out exactly where all the auxiliary programs
98 are, and initialises mutable variables to make it easy to call them.
99 To to this, it makes use of definitions in Config.hs, which is a Haskell
100 file containing variables whose value is figured out by the build system.
101
102 Config.hs contains two sorts of things
103
104   cGCC,         The *names* of the programs
105   cCPP            e.g.  cGCC = gcc
106   cUNLIT                cCPP = gcc -E
107   etc           They do *not* include paths
108
109
110   cUNLIT_DIR   The *path* to the directory containing unlit, split etc
111   cSPLIT_DIR   *relative* to the root of the build tree,
112                    for use when running *in-place* in a build tree (only)
113
114
115
116 ---------------------------------------------
117 NOTES for an ALTERNATIVE scheme (i.e *not* what is currently implemented):
118
119 Another hair-brained scheme for simplifying the current tool location
120 nightmare in GHC: Simon originally suggested using another
121 configuration file along the lines of GCC's specs file - which is fine
122 except that it means adding code to read yet another configuration
123 file.  What I didn't notice is that the current package.conf is
124 general enough to do this:
125
126 Package
127     {name = "tools",    import_dirs = [],  source_dirs = [],
128      library_dirs = [], hs_libraries = [], extra_libraries = [],
129      include_dirs = [], c_includes = [],   package_deps = [],
130      extra_ghc_opts = ["-pgmc/usr/bin/gcc","-pgml${topdir}/bin/unlit", ... etc.],
131      extra_cc_opts = [], extra_ld_opts = []}
132
133 Which would have the advantage that we get to collect together in one
134 place the path-specific package stuff with the path-specific tool
135 stuff.
136                 End of NOTES
137 ---------------------------------------------
138
139 %************************************************************************
140 %*                                                                      *
141 \subsection{Initialisation}
142 %*                                                                      *
143 %************************************************************************
144
145 \begin{code}
146 initSysTools :: Maybe String    -- Maybe TopDir path (without the '-B' prefix)
147
148              -> DynFlags
149              -> IO DynFlags     -- Set all the mutable variables above, holding
150                                 --      (a) the system programs
151                                 --      (b) the package-config file
152                                 --      (c) the GHC usage message
153
154
155 initSysTools mbMinusB dflags0
156   = do  { top_dir <- findTopDir mbMinusB
157                 -- see [Note topdir]
158                 -- NB: top_dir is assumed to be in standard Unix
159                 -- format, '/' separated
160
161         ; let installed :: FilePath -> FilePath
162               installed file = top_dir </> file
163               installed_mingw_bin file = top_dir </> ".." </> "mingw" </> "bin" </> file
164               installed_perl_bin file = top_dir </> ".." </> "perl" </> file
165
166         ; let pkgconfig_path = installed "package.conf.d"
167               ghc_usage_msg_path  = installed "ghc-usage.txt"
168               ghci_usage_msg_path = installed "ghci-usage.txt"
169
170                 -- For all systems, unlit, split, mangle are GHC utilities
171                 -- architecture-specific stuff is done when building Config.hs
172               unlit_path = installed cGHC_UNLIT_PGM
173
174                 -- split is a Perl script
175               split_script  = installed cGHC_SPLIT_PGM
176
177               windres_path  = installed_mingw_bin "windres"
178
179         ; tmpdir <- getTemporaryDirectory
180         ; let dflags1 = setTmpDir tmpdir dflags0
181
182         -- On Windows, mingw is distributed with GHC,
183         --      so we look in TopDir/../mingw/bin
184         ; let
185               gcc_prog
186                 | isWindowsHost = installed_mingw_bin "gcc"
187                 | otherwise     = cGCC
188               perl_path
189                 | isWindowsHost = installed_perl_bin cGHC_PERL
190                 | otherwise     = cGHC_PERL
191               -- 'touch' is a GHC util for Windows
192               touch_path
193                 | isWindowsHost = installed cGHC_TOUCHY_PGM
194                 | otherwise     = "touch"
195               -- On Win32 we don't want to rely on #!/bin/perl, so we prepend
196               -- a call to Perl to get the invocation of split.
197               -- On Unix, scripts are invoked using the '#!' method.  Binary
198               -- installations of GHC on Unix place the correct line on the
199               -- front of the script at installation time, so we don't want
200               -- to wire-in our knowledge of $(PERL) on the host system here.
201               (split_prog,  split_args)
202                 | isWindowsHost = (perl_path,    [Option split_script])
203                 | otherwise     = (split_script, [])
204               (mkdll_prog, mkdll_args)
205                 | not isWindowsHost
206                     = panic "Can't build DLLs on a non-Win32 system"
207                 | otherwise =
208                     (installed_mingw_bin cMKDLL, [])
209
210         -- cpp is derived from gcc on all platforms
211         -- HACK, see setPgmP below. We keep 'words' here to remember to fix
212         -- Config.hs one day.
213         ; let cpp_path  = (gcc_prog,
214                            (Option "-E"):(map Option (words cRAWCPP_FLAGS)))
215
216         -- Other things being equal, as and ld are simply gcc
217         ; let   as_prog  = gcc_prog
218                 ld_prog  = gcc_prog
219
220         -- figure out llvm location. (TODO: Acutally implement).
221         ; let lc_prog = "llc"
222               lo_prog = "opt"
223
224         ; return dflags1{
225                         ghcUsagePath = ghc_usage_msg_path,
226                         ghciUsagePath = ghci_usage_msg_path,
227                         topDir  = top_dir,
228                         systemPackageConfig = pkgconfig_path,
229                         pgm_L   = unlit_path,
230                         pgm_P   = cpp_path,
231                         pgm_F   = "",
232                         pgm_c   = (gcc_prog,[]),
233                         pgm_s   = (split_prog,split_args),
234                         pgm_a   = (as_prog,[]),
235                         pgm_l   = (ld_prog,[]),
236                         pgm_dll = (mkdll_prog,mkdll_args),
237                         pgm_T   = touch_path,
238                         pgm_sysman = top_dir ++ "/ghc/rts/parallel/SysMan",
239                         pgm_windres = windres_path,
240                         pgm_lo  = (lo_prog,[]),
241                         pgm_lc  = (lc_prog,[])
242                         -- Hans: this isn't right in general, but you can
243                         -- elaborate it in the same way as the others
244                 }
245         }
246 \end{code}
247
248 \begin{code}
249 -- returns a Unix-format path (relying on getBaseDir to do so too)
250 findTopDir :: Maybe String -- Maybe TopDir path (without the '-B' prefix).
251            -> IO String    -- TopDir (in Unix format '/' separated)
252 findTopDir (Just minusb) = return (normalise minusb)
253 findTopDir Nothing
254     = do -- Get directory of executable
255          maybe_exec_dir <- getBaseDir
256          case maybe_exec_dir of
257              -- "Just" on Windows, "Nothing" on unix
258              Nothing  -> ghcError (InstallationError "missing -B<dir> option")
259              Just dir -> return dir
260 \end{code}
261
262
263 %************************************************************************
264 %*                                                                      *
265 \subsection{Running an external program}
266 %*                                                                      *
267 %************************************************************************
268
269
270 \begin{code}
271 runUnlit :: DynFlags -> [Option] -> IO ()
272 runUnlit dflags args = do
273   let p = pgm_L dflags
274   runSomething dflags "Literate pre-processor" p args
275
276 runCpp :: DynFlags -> [Option] -> IO ()
277 runCpp dflags args =   do
278   let (p,args0) = pgm_P dflags
279       args1 = args0 ++ args
280       args2 = if dopt Opt_WarnIsError dflags
281               then Option "-Werror" : args1
282               else                    args1
283   mb_env <- getGccEnv args2
284   runSomethingFiltered dflags id  "C pre-processor" p args2 mb_env
285
286 runPp :: DynFlags -> [Option] -> IO ()
287 runPp dflags args =   do
288   let p = pgm_F dflags
289   runSomething dflags "Haskell pre-processor" p args
290
291 runCc :: DynFlags -> [Option] -> IO ()
292 runCc dflags args =   do
293   let (p,args0) = pgm_c dflags
294       args1 = args0 ++ args
295   mb_env <- getGccEnv args1
296   runSomethingFiltered dflags cc_filter "C Compiler" p args1 mb_env
297  where
298   -- discard some harmless warnings from gcc that we can't turn off
299   cc_filter = unlines . doFilter . lines
300
301   {-
302   gcc gives warnings in chunks like so:
303       In file included from /foo/bar/baz.h:11,
304                        from /foo/bar/baz2.h:22,
305                        from wibble.c:33:
306       /foo/flibble:14: global register variable ...
307       /foo/flibble:15: warning: call-clobbered r...
308   We break it up into its chunks, remove any call-clobbered register
309   warnings from each chunk, and then delete any chunks that we have
310   emptied of warnings.
311   -}
312   doFilter = unChunkWarnings . filterWarnings . chunkWarnings []
313   -- We can't assume that the output will start with an "In file inc..."
314   -- line, so we start off expecting a list of warnings rather than a
315   -- location stack.
316   chunkWarnings :: [String] -- The location stack to use for the next
317                             -- list of warnings
318                 -> [String] -- The remaining lines to look at
319                 -> [([String], [String])]
320   chunkWarnings loc_stack [] = [(loc_stack, [])]
321   chunkWarnings loc_stack xs
322       = case break loc_stack_start xs of
323         (warnings, lss:xs') ->
324             case span loc_start_continuation xs' of
325             (lsc, xs'') ->
326                 (loc_stack, warnings) : chunkWarnings (lss : lsc) xs''
327         _ -> [(loc_stack, xs)]
328
329   filterWarnings :: [([String], [String])] -> [([String], [String])]
330   filterWarnings [] = []
331   -- If the warnings are already empty then we are probably doing
332   -- something wrong, so don't delete anything
333   filterWarnings ((xs, []) : zs) = (xs, []) : filterWarnings zs
334   filterWarnings ((xs, ys) : zs) = case filter wantedWarning ys of
335                                        [] -> filterWarnings zs
336                                        ys' -> (xs, ys') : filterWarnings zs
337
338   unChunkWarnings :: [([String], [String])] -> [String]
339   unChunkWarnings [] = []
340   unChunkWarnings ((xs, ys) : zs) = xs ++ ys ++ unChunkWarnings zs
341
342   loc_stack_start        s = "In file included from " `isPrefixOf` s
343   loc_start_continuation s = "                 from " `isPrefixOf` s
344   wantedWarning w
345    | "warning: call-clobbered register used" `isContainedIn` w = False
346    | otherwise = True
347
348 isContainedIn :: String -> String -> Bool
349 xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
350
351 -- If the -B<dir> option is set, add <dir> to PATH.  This works around
352 -- a bug in gcc on Windows Vista where it can't find its auxiliary
353 -- binaries (see bug #1110).
354 getGccEnv :: [Option] -> IO (Maybe [(String,String)])
355 getGccEnv opts =
356   if null b_dirs
357      then return Nothing
358      else do env <- getEnvironment
359              return (Just (map mangle_path env))
360  where
361   (b_dirs, _) = partitionWith get_b_opt opts
362
363   get_b_opt (Option ('-':'B':dir)) = Left dir
364   get_b_opt other = Right other
365
366   mangle_path (path,paths) | map toUpper path == "PATH"
367         = (path, '\"' : head b_dirs ++ "\";" ++ paths)
368   mangle_path other = other
369
370 runSplit :: DynFlags -> [Option] -> IO ()
371 runSplit dflags args = do
372   let (p,args0) = pgm_s dflags
373   runSomething dflags "Splitter" p (args0++args)
374
375 runAs :: DynFlags -> [Option] -> IO ()
376 runAs dflags args = do
377   let (p,args0) = pgm_a dflags
378       args1 = args0 ++ args
379   mb_env <- getGccEnv args1
380   runSomethingFiltered dflags id "Assembler" p args1 mb_env
381
382 runLlvmOpt :: DynFlags -> [Option] -> IO ()
383 runLlvmOpt dflags args = do
384   let (p,args0) = pgm_lo dflags
385   runSomething dflags "LLVM Optimiser" p (args0++args)
386
387 runLlvmLlc :: DynFlags -> [Option] -> IO ()
388 runLlvmLlc dflags args = do
389   let (p,args0) = pgm_lc dflags
390   runSomething dflags "LLVM Compiler" p (args0++args)
391
392 runLink :: DynFlags -> [Option] -> IO ()
393 runLink dflags args = do
394   let (p,args0) = pgm_l dflags
395       args1 = args0 ++ args
396   mb_env <- getGccEnv args1
397   runSomethingFiltered dflags id "Linker" p args1 mb_env
398
399 runMkDLL :: DynFlags -> [Option] -> IO ()
400 runMkDLL dflags args = do
401   let (p,args0) = pgm_dll dflags
402       args1 = args0 ++ args
403   mb_env <- getGccEnv (args0++args)
404   runSomethingFiltered dflags id "Make DLL" p args1 mb_env
405
406 runWindres :: DynFlags -> [Option] -> IO ()
407 runWindres dflags args = do
408   let (gcc, gcc_args) = pgm_c dflags
409       windres = pgm_windres dflags
410       quote x = "\"" ++ x ++ "\""
411       args' = -- If windres.exe and gcc.exe are in a directory containing
412               -- spaces then windres fails to run gcc. We therefore need
413               -- to tell it what command to use...
414               Option ("--preprocessor=" ++
415                       unwords (map quote (gcc :
416                                           map showOpt gcc_args ++
417                                           ["-E", "-xc", "-DRC_INVOKED"])))
418               -- ...but if we do that then if windres calls popen then
419               -- it can't understand the quoting, so we have to use
420               -- --use-temp-file so that it interprets it correctly.
421               -- See #1828.
422             : Option "--use-temp-file"
423             : args
424   mb_env <- getGccEnv gcc_args
425   runSomethingFiltered dflags id "Windres" windres args' mb_env
426
427 touch :: DynFlags -> String -> String -> IO ()
428 touch dflags purpose arg =
429   runSomething dflags purpose (pgm_T dflags) [FileOption "" arg]
430
431 copy :: DynFlags -> String -> FilePath -> FilePath -> IO ()
432 copy dflags purpose from to = copyWithHeader dflags purpose Nothing from to
433
434 copyWithHeader :: DynFlags -> String -> Maybe String -> FilePath -> FilePath
435                -> IO ()
436 copyWithHeader dflags purpose maybe_header from to = do
437   showPass dflags purpose
438
439   hout <- openBinaryFile to   WriteMode
440   hin  <- openBinaryFile from ReadMode
441   ls <- hGetContents hin -- inefficient, but it'll do for now. ToDo: speed up
442   maybe (return ()) (hPutStr hout) maybe_header
443   hPutStr hout ls
444   hClose hout
445   hClose hin
446
447 getExtraViaCOpts :: DynFlags -> IO [String]
448 getExtraViaCOpts dflags = do
449   f <- readFile (topDir dflags </> "extra-gcc-opts")
450   return (words f)
451 \end{code}
452
453 %************************************************************************
454 %*                                                                      *
455 \subsection{Managing temporary files
456 %*                                                                      *
457 %************************************************************************
458
459 \begin{code}
460 cleanTempDirs :: DynFlags -> IO ()
461 cleanTempDirs dflags
462    = unless (dopt Opt_KeepTmpFiles dflags)
463    $ do let ref = dirsToClean dflags
464         ds <- readIORef ref
465         removeTmpDirs dflags (Map.elems ds)
466         writeIORef ref Map.empty
467
468 cleanTempFiles :: DynFlags -> IO ()
469 cleanTempFiles dflags
470    = unless (dopt Opt_KeepTmpFiles dflags)
471    $ do let ref = filesToClean dflags
472         fs <- readIORef ref
473         removeTmpFiles dflags fs
474         writeIORef ref []
475
476 cleanTempFilesExcept :: DynFlags -> [FilePath] -> IO ()
477 cleanTempFilesExcept dflags dont_delete
478    = unless (dopt Opt_KeepTmpFiles dflags)
479    $ do let ref = filesToClean dflags
480         files <- readIORef ref
481         let (to_keep, to_delete) = partition (`elem` dont_delete) files
482         removeTmpFiles dflags to_delete
483         writeIORef ref to_keep
484
485
486 -- find a temporary name that doesn't already exist.
487 newTempName :: DynFlags -> Suffix -> IO FilePath
488 newTempName dflags extn
489   = do d <- getTempDir dflags
490        x <- getProcessID
491        findTempName (d </> "ghc" ++ show x ++ "_") 0
492   where
493     findTempName :: FilePath -> Integer -> IO FilePath
494     findTempName prefix x
495       = do let filename = (prefix ++ show x) <.> extn
496            b  <- doesFileExist filename
497            if b then findTempName prefix (x+1)
498                 else do -- clean it up later
499                         consIORef (filesToClean dflags) filename
500                         return filename
501
502 -- return our temporary directory within tmp_dir, creating one if we
503 -- don't have one yet
504 getTempDir :: DynFlags -> IO FilePath
505 getTempDir dflags@(DynFlags{tmpDir=tmp_dir})
506   = do let ref = dirsToClean dflags
507        mapping <- readIORef ref
508        case Map.lookup tmp_dir mapping of
509            Nothing ->
510                do x <- getProcessID
511                   let prefix = tmp_dir </> "ghc" ++ show x ++ "_"
512                   let
513                       mkTempDir :: Integer -> IO FilePath
514                       mkTempDir x
515                        = let dirname = prefix ++ show x
516                          in do createDirectory dirname
517                                let mapping' = Map.insert tmp_dir dirname mapping
518                                writeIORef ref mapping'
519                                debugTraceMsg dflags 2 (ptext (sLit "Created temporary directory:") <+> text dirname)
520                                return dirname
521                             `catchIO` \e ->
522                                     if isAlreadyExistsError e
523                                     then mkTempDir (x+1)
524                                     else ioError e
525                   mkTempDir 0
526            Just d -> return d
527
528 addFilesToClean :: DynFlags -> [FilePath] -> IO ()
529 -- May include wildcards [used by DriverPipeline.run_phase SplitMangle]
530 addFilesToClean dflags files = mapM_ (consIORef (filesToClean dflags)) files
531
532 removeTmpDirs :: DynFlags -> [FilePath] -> IO ()
533 removeTmpDirs dflags ds
534   = traceCmd dflags "Deleting temp dirs"
535              ("Deleting: " ++ unwords ds)
536              (mapM_ (removeWith dflags removeDirectory) ds)
537
538 removeTmpFiles :: DynFlags -> [FilePath] -> IO ()
539 removeTmpFiles dflags fs
540   = warnNon $
541     traceCmd dflags "Deleting temp files"
542              ("Deleting: " ++ unwords deletees)
543              (mapM_ (removeWith dflags removeFile) deletees)
544   where
545      -- Flat out refuse to delete files that are likely to be source input
546      -- files (is there a worse bug than having a compiler delete your source
547      -- files?)
548      --
549      -- Deleting source files is a sign of a bug elsewhere, so prominently flag
550      -- the condition.
551     warnNon act
552      | null non_deletees = act
553      | otherwise         = do
554         putMsg dflags (text "WARNING - NOT deleting source files:" <+> hsep (map text non_deletees))
555         act
556
557     (non_deletees, deletees) = partition isHaskellUserSrcFilename fs
558
559 removeWith :: DynFlags -> (FilePath -> IO ()) -> FilePath -> IO ()
560 removeWith dflags remover f = remover f `catchIO`
561   (\e ->
562    let msg = if isDoesNotExistError e
563              then ptext (sLit "Warning: deleting non-existent") <+> text f
564              else ptext (sLit "Warning: exception raised when deleting")
565                                             <+> text f <> colon
566                $$ text (show e)
567    in debugTraceMsg dflags 2 msg
568   )
569
570 -----------------------------------------------------------------------------
571 -- Running an external program
572
573 runSomething :: DynFlags
574              -> String          -- For -v message
575              -> String          -- Command name (possibly a full path)
576                                 --      assumed already dos-ified
577              -> [Option]        -- Arguments
578                                 --      runSomething will dos-ify them
579              -> IO ()
580
581 runSomething dflags phase_name pgm args =
582   runSomethingFiltered dflags id phase_name pgm args Nothing
583
584 runSomethingFiltered
585   :: DynFlags -> (String->String) -> String -> String -> [Option]
586   -> Maybe [(String,String)] -> IO ()
587
588 runSomethingFiltered dflags filter_fn phase_name pgm args mb_env = do
589   let real_args = filter notNull (map showOpt args)
590 #if __GLASGOW_HASKELL__ >= 701
591       cmdLine = showCommandForUser pgm real_args
592 #else
593       cmdLine = unwords (pgm:real_args)
594 #endif
595   traceCmd dflags phase_name cmdLine $ do
596   (exit_code, doesn'tExist) <-
597      catchIO (do
598          rc <- builderMainLoop dflags filter_fn pgm real_args mb_env
599          case rc of
600            ExitSuccess{} -> return (rc, False)
601            ExitFailure n
602              -- rawSystem returns (ExitFailure 127) if the exec failed for any
603              -- reason (eg. the program doesn't exist).  This is the only clue
604              -- we have, but we need to report something to the user because in
605              -- the case of a missing program there will otherwise be no output
606              -- at all.
607             | n == 127  -> return (rc, True)
608             | otherwise -> return (rc, False))
609                 -- Should 'rawSystem' generate an IO exception indicating that
610                 -- 'pgm' couldn't be run rather than a funky return code, catch
611                 -- this here (the win32 version does this, but it doesn't hurt
612                 -- to test for this in general.)
613               (\ err ->
614                 if IO.isDoesNotExistError err
615                  then return (ExitFailure 1, True)
616                  else IO.ioError err)
617   case (doesn'tExist, exit_code) of
618      (True, _)        -> ghcError (InstallationError ("could not execute: " ++ pgm))
619      (_, ExitSuccess) -> return ()
620      _                -> ghcError (PhaseFailed phase_name exit_code)
621
622 builderMainLoop :: DynFlags -> (String -> String) -> FilePath
623                 -> [String] -> Maybe [(String, String)]
624                 -> IO ExitCode
625 builderMainLoop dflags filter_fn pgm real_args mb_env = do
626   chan <- newChan
627   (hStdIn, hStdOut, hStdErr, hProcess) <- runInteractiveProcess pgm real_args Nothing mb_env
628
629   -- and run a loop piping the output from the compiler to the log_action in DynFlags
630   hSetBuffering hStdOut LineBuffering
631   hSetBuffering hStdErr LineBuffering
632   _ <- forkIO (readerProc chan hStdOut filter_fn)
633   _ <- forkIO (readerProc chan hStdErr filter_fn)
634   -- we don't want to finish until 2 streams have been completed
635   -- (stdout and stderr)
636   -- nor until 1 exit code has been retrieved.
637   rc <- loop chan hProcess (2::Integer) (1::Integer) ExitSuccess
638   -- after that, we're done here.
639   hClose hStdIn
640   hClose hStdOut
641   hClose hStdErr
642   return rc
643   where
644     -- status starts at zero, and increments each time either
645     -- a reader process gets EOF, or the build proc exits.  We wait
646     -- for all of these to happen (status==3).
647     -- ToDo: we should really have a contingency plan in case any of
648     -- the threads dies, such as a timeout.
649     loop _    _        0 0 exitcode = return exitcode
650     loop chan hProcess t p exitcode = do
651       mb_code <- if p > 0
652                    then getProcessExitCode hProcess
653                    else return Nothing
654       case mb_code of
655         Just code -> loop chan hProcess t (p-1) code
656         Nothing
657           | t > 0 -> do
658               msg <- readChan chan
659               case msg of
660                 BuildMsg msg -> do
661                   log_action dflags SevInfo noSrcSpan defaultUserStyle msg
662                   loop chan hProcess t p exitcode
663                 BuildError loc msg -> do
664                   log_action dflags SevError (mkSrcSpan loc loc) defaultUserStyle msg
665                   loop chan hProcess t p exitcode
666                 EOF ->
667                   loop chan hProcess (t-1) p exitcode
668           | otherwise -> loop chan hProcess t p exitcode
669
670 readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO ()
671 readerProc chan hdl filter_fn =
672     (do str <- hGetContents hdl
673         loop (linesPlatform (filter_fn str)) Nothing)
674     `finally`
675        writeChan chan EOF
676         -- ToDo: check errors more carefully
677         -- ToDo: in the future, the filter should be implemented as
678         -- a stream transformer.
679     where
680         loop []     Nothing    = return ()
681         loop []     (Just err) = writeChan chan err
682         loop (l:ls) in_err     =
683                 case in_err of
684                   Just err@(BuildError srcLoc msg)
685                     | leading_whitespace l -> do
686                         loop ls (Just (BuildError srcLoc (msg $$ text l)))
687                     | otherwise -> do
688                         writeChan chan err
689                         checkError l ls
690                   Nothing -> do
691                         checkError l ls
692                   _ -> panic "readerProc/loop"
693
694         checkError l ls
695            = case parseError l of
696                 Nothing -> do
697                     writeChan chan (BuildMsg (text l))
698                     loop ls Nothing
699                 Just (file, lineNum, colNum, msg) -> do
700                     let srcLoc = mkSrcLoc (mkFastString file) lineNum colNum
701                     loop ls (Just (BuildError srcLoc (text msg)))
702
703         leading_whitespace []    = False
704         leading_whitespace (x:_) = isSpace x
705
706 parseError :: String -> Maybe (String, Int, Int, String)
707 parseError s0 = case breakColon s0 of
708                 Just (filename, s1) ->
709                     case breakIntColon s1 of
710                     Just (lineNum, s2) ->
711                         case breakIntColon s2 of
712                         Just (columnNum, s3) ->
713                             Just (filename, lineNum, columnNum, s3)
714                         Nothing ->
715                             Just (filename, lineNum, 0, s2)
716                     Nothing -> Nothing
717                 Nothing -> Nothing
718
719 breakColon :: String -> Maybe (String, String)
720 breakColon xs = case break (':' ==) xs of
721                     (ys, _:zs) -> Just (ys, zs)
722                     _ -> Nothing
723
724 breakIntColon :: String -> Maybe (Int, String)
725 breakIntColon xs = case break (':' ==) xs of
726                        (ys, _:zs)
727                         | not (null ys) && all isAscii ys && all isDigit ys ->
728                            Just (read ys, zs)
729                        _ -> Nothing
730
731 data BuildMessage
732   = BuildMsg   !SDoc
733   | BuildError !SrcLoc !SDoc
734   | EOF
735
736 traceCmd :: DynFlags -> String -> String -> IO () -> IO ()
737 -- a) trace the command (at two levels of verbosity)
738 -- b) don't do it at all if dry-run is set
739 traceCmd dflags phase_name cmd_line action
740  = do   { let verb = verbosity dflags
741         ; showPass dflags phase_name
742         ; debugTraceMsg dflags 3 (text cmd_line)
743         ; hFlush stderr
744
745            -- Test for -n flag
746         ; unless (dopt Opt_DryRun dflags) $ do {
747
748            -- And run it!
749         ; action `catchIO` handle_exn verb
750         }}
751   where
752     handle_exn _verb exn = do { debugTraceMsg dflags 2 (char '\n')
753                               ; debugTraceMsg dflags 2 (ptext (sLit "Failed:") <+> text cmd_line <+> text (show exn))
754                               ; ghcError (PhaseFailed phase_name (ExitFailure 1)) }
755 \end{code}
756
757 %************************************************************************
758 %*                                                                      *
759 \subsection{Support code}
760 %*                                                                      *
761 %************************************************************************
762
763 \begin{code}
764 -----------------------------------------------------------------------------
765 -- Define       getBaseDir     :: IO (Maybe String)
766
767 getBaseDir :: IO (Maybe String)
768 #if defined(mingw32_HOST_OS)
769 -- Assuming we are running ghc, accessed by path  $(stuff)/bin/ghc.exe,
770 -- return the path $(stuff)/lib.
771 getBaseDir = do let len = (2048::Int) -- plenty, PATH_MAX is 512 under Win32.
772                 buf <- mallocArray len
773                 ret <- getModuleFileName nullPtr buf len
774                 if ret == 0 then free buf >> return Nothing
775                             else do s <- peekCString buf
776                                     free buf
777                                     return (Just (rootDir s))
778   where
779     rootDir s = case splitFileName $ normalise s of
780                 (d, ghc_exe)
781                  | lower ghc_exe `elem` ["ghc.exe",
782                                          "ghc-stage1.exe",
783                                          "ghc-stage2.exe",
784                                          "ghc-stage3.exe"] ->
785                     case splitFileName $ takeDirectory d of
786                     -- ghc is in $topdir/bin/ghc.exe
787                     (d', bin) | lower bin == "bin" -> takeDirectory d' </> "lib"
788                     _ -> fail
789                 _ -> fail
790         where fail = panic ("can't decompose ghc.exe path: " ++ show s)
791               lower = map toLower
792
793 foreign import stdcall unsafe "GetModuleFileNameA"
794   getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
795 #else
796 getBaseDir = return Nothing
797 #endif
798
799 #ifdef mingw32_HOST_OS
800 foreign import ccall unsafe "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
801 #else
802 getProcessID :: IO Int
803 getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral
804 #endif
805
806 -- Divvy up text stream into lines, taking platform dependent
807 -- line termination into account.
808 linesPlatform :: String -> [String]
809 #if !defined(mingw32_HOST_OS)
810 linesPlatform ls = lines ls
811 #else
812 linesPlatform "" = []
813 linesPlatform xs =
814   case lineBreak xs of
815     (as,xs1) -> as : linesPlatform xs1
816   where
817    lineBreak "" = ("","")
818    lineBreak ('\r':'\n':xs) = ([],xs)
819    lineBreak ('\n':xs) = ([],xs)
820    lineBreak (x:xs) = let (as,bs) = lineBreak xs in (x:as,bs)
821
822 #endif
823
824 \end{code}