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