More build system changes; ghc-pkg is now built with Cabal
[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 {-# OPTIONS -fno-cse #-}
11 -- -fno-cse is needed for GLOBAL_VAR's to behave properly
12
13 module SysTools (
14         -- Initialisation
15         initSysTools,
16
17         -- Interface to system tools
18         runUnlit, runCpp, runCc, -- [Option] -> IO ()
19         runPp,                   -- [Option] -> IO ()
20         runMangle, runSplit,     -- [Option] -> IO ()
21         runAs, runLink,          -- [Option] -> IO ()
22         runMkDLL,
23         runWindres,
24
25         touch,                  -- String -> String -> IO ()
26         copy,
27         copyWithHeader,
28         getExtraViaCOpts,
29
30         -- Temporary-file management
31         setTmpDir,
32         newTempName,
33         cleanTempDirs, cleanTempFiles, cleanTempFilesExcept,
34         addFilesToClean,
35
36         Option(..)
37
38  ) where
39
40 #include "HsVersions.h"
41
42 import DriverPhases
43 import Config
44 import Outputable
45 import ErrUtils
46 import Panic
47 import Util
48 import DynFlags
49 import FiniteMap
50
51 import Control.Exception
52 import Data.IORef
53 import Control.Monad
54 import System.Exit
55 import System.Environment
56 import System.FilePath
57 import System.IO
58 import System.IO.Error as IO
59 import System.Directory
60 import Data.Char
61 import Data.Maybe
62 import Data.List
63
64 #ifndef mingw32_HOST_OS
65 import qualified System.Posix.Internals
66 #else /* Must be Win32 */
67 import Foreign
68 import CString          ( CString, peekCString )
69 #endif
70
71 import System.Process   ( runInteractiveProcess, getProcessExitCode )
72 import Control.Concurrent
73 import FastString
74 import SrcLoc           ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan )
75 \end{code}
76
77
78                 The configuration story
79                 ~~~~~~~~~~~~~~~~~~~~~~~
80
81 GHC needs various support files (library packages, RTS etc), plus
82 various auxiliary programs (cp, gcc, etc).  It finds these in one
83 of two places:
84
85 * When running as an *installed program*, GHC finds most of this support
86   stuff in the installed library tree.  The path to this tree is passed
87   to GHC via the -B flag, and given to initSysTools .
88
89 * When running *in-place* in a build tree, GHC finds most of this support
90   stuff in the build tree.  The path to the build tree is, again passed
91   to GHC via -B.
92
93 GHC tells which of the two is the case by seeing whether package.conf
94 is in TopDir [installed] or in TopDir/ghc/driver [inplace] (what a hack).
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_REL   The *path* to the directory containing unlit, split etc
111   cSPLIT_DIR_REL   *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  { (am_installed, top_dir) <- findTopDir mbMinusB
157                 -- top_dir
158                 --      for "installed" this is the root of GHC's support files
159                 --      for "in-place" it is the root of the build tree
160                 -- NB: top_dir is assumed to be in standard Unix
161                 -- format, '/' separated
162
163         ; let installed, installed_bin :: FilePath -> FilePath
164               installed_bin pgm  = top_dir </> pgm
165               installed     file = top_dir </> file
166               real_top_dir
167                | isWindowsHost = top_dir </> ".." </> ".."
168                | otherwise     = top_dir </> ".."
169               inplace dir   pgm  = real_top_dir </> dir </> pgm
170
171         ; let pkgconfig_path
172                 | am_installed = installed "package.conf"
173                 | otherwise    = inplace "inplace-datadir" "package.conf"
174
175               ghc_usage_msg_path
176                 | am_installed = installed "ghc-usage.txt"
177                 | otherwise    = inplace cGHC_DRIVER_DIR_REL "ghc-usage.txt"
178
179               ghci_usage_msg_path
180                 | am_installed = installed "ghci-usage.txt"
181                 | otherwise    = inplace cGHC_DRIVER_DIR_REL "ghci-usage.txt"
182
183                 -- For all systems, unlit, split, mangle are GHC utilities
184                 -- architecture-specific stuff is done when building Config.hs
185               unlit_path
186                 | am_installed = installed_bin cGHC_UNLIT_PGM
187                 | otherwise    = inplace cGHC_UNLIT_DIR_REL cGHC_UNLIT_PGM
188
189                 -- split and mangle are Perl scripts
190               split_script
191                 | am_installed = installed_bin cGHC_SPLIT_PGM
192                 | otherwise    = inplace cGHC_SPLIT_DIR_REL cGHC_SPLIT_PGM
193
194               mangle_script
195                 | am_installed = installed_bin cGHC_MANGLER_PGM
196                 | otherwise    = inplace cGHC_MANGLER_DIR_REL cGHC_MANGLER_PGM
197
198               windres_path
199                 | am_installed = installed_bin "bin/windres"
200                 | otherwise    = "windres"
201
202         ; tmpdir <- getTemporaryDirectory
203         ; let dflags1 = setTmpDir tmpdir dflags0
204
205         -- Check that the package config exists
206         ; config_exists <- doesFileExist pkgconfig_path
207         ; when (not config_exists) $
208              throwDyn (InstallationError
209                          ("Can't find package.conf as " ++ pkgconfig_path))
210
211         -- On Windows, gcc and friends are distributed with GHC,
212         --      so when "installed" we look in TopDir/bin
213         -- When "in-place", or when not on Windows, we look wherever
214         --      the build-time configure script found them
215         ; let
216               -- The trailing "/" is absolutely essential; gcc seems
217               -- to construct file names simply by concatenating to
218               -- this -B path with no extra slash We use "/" rather
219               -- than "\\" because otherwise "\\\" is mangled
220               -- later on; although gcc_args are in NATIVE format,
221               -- gcc can cope
222               --      (see comments with declarations of global variables)
223               gcc_b_arg = Option ("-B" ++ installed "gcc-lib/")
224               (gcc_prog,gcc_args)
225                 | isWindowsHost && am_installed
226                     -- We tell gcc where its specs file + exes are (-B)
227                     -- and also some places to pick up include files.  We need
228                     -- to be careful to put all necessary exes in the -B place
229                     -- (as, ld, cc1, etc) since if they don't get found there,
230                     -- gcc then tries to run unadorned "as", "ld", etc, and
231                     -- will pick up whatever happens to be lying around in
232                     -- the path, possibly including those from a cygwin
233                     -- install on the target, which is exactly what we're
234                     -- trying to avoid.
235                     = (installed_bin "gcc", [gcc_b_arg])
236                 | otherwise = (cGCC, [])
237               perl_path
238                 | isWindowsHost && am_installed = installed_bin cGHC_PERL
239                 | otherwise = cGHC_PERL
240               -- 'touch' is a GHC util for Windows
241               touch_path
242                 | isWindowsHost
243                     = if am_installed
244                       then installed_bin cGHC_TOUCHY_PGM
245                       else inplace cGHC_TOUCHY_DIR_REL cGHC_TOUCHY_PGM
246                 | otherwise = "touch"
247               -- On Win32 we don't want to rely on #!/bin/perl, so we prepend
248               -- a call to Perl to get the invocation of split and mangle.
249               -- On Unix, scripts are invoked using the '#!' method.  Binary
250               -- installations of GHC on Unix place the correct line on the
251               -- front of the script at installation time, so we don't want
252               -- to wire-in our knowledge of $(PERL) on the host system here.
253               (split_prog,  split_args)
254                 | isWindowsHost = (perl_path,    [Option split_script])
255                 | otherwise     = (split_script, [])
256               (mangle_prog, mangle_args)
257                 | isWindowsHost = (perl_path,   [Option mangle_script])
258                 | otherwise     = (mangle_script, [])
259               (mkdll_prog, mkdll_args)
260                 | not isWindowsHost
261                     = panic "Can't build DLLs on a non-Win32 system"
262                 | am_installed =
263                     (installed "gcc-lib/" </> cMKDLL,
264                      [ Option "--dlltool-name",
265                        Option (installed "gcc-lib/" </> "dlltool"),
266                        Option "--driver-name",
267                        Option gcc_prog, gcc_b_arg ])
268                 | otherwise    = (cMKDLL, [])
269
270         -- cpp is derived from gcc on all platforms
271         -- HACK, see setPgmP below. We keep 'words' here to remember to fix
272         -- Config.hs one day.
273         ; let cpp_path  = (gcc_prog, gcc_args ++
274                            (Option "-E"):(map Option (words cRAWCPP_FLAGS)))
275
276         -- Other things being equal, as and ld are simply gcc
277         ; let   (as_prog,as_args)  = (gcc_prog,gcc_args)
278                 (ld_prog,ld_args)  = (gcc_prog,gcc_args)
279
280         ; return dflags1{
281                         ghcUsagePath = ghc_usage_msg_path,
282                         ghciUsagePath = ghci_usage_msg_path,
283                         topDir  = top_dir,
284                         systemPackageConfig = pkgconfig_path,
285                         pgm_L   = unlit_path,
286                         pgm_P   = cpp_path,
287                         pgm_F   = "",
288                         pgm_c   = (gcc_prog,gcc_args),
289                         pgm_m   = (mangle_prog,mangle_args),
290                         pgm_s   = (split_prog,split_args),
291                         pgm_a   = (as_prog,as_args),
292                         pgm_l   = (ld_prog,ld_args),
293                         pgm_dll = (mkdll_prog,mkdll_args),
294                         pgm_T   = touch_path,
295                         pgm_sysman = top_dir ++ "/ghc/rts/parallel/SysMan",
296                         pgm_windres = windres_path
297                         -- Hans: this isn't right in general, but you can
298                         -- elaborate it in the same way as the others
299                 }
300         }
301 \end{code}
302
303 \begin{code}
304 -- Find TopDir
305 --      for "installed" this is the root of GHC's support files
306 --      for "in-place" it is the root of the build tree
307 --
308 -- Plan of action:
309 -- 1. Set proto_top_dir
310 --      if there is no given TopDir path, get the directory
311 --      where GHC is running (only on Windows)
312 --
313 -- 2. If package.conf exists in proto_top_dir, we are running
314 --      installed; and TopDir = proto_top_dir
315 --
316 -- 3. Otherwise we are running in-place, so
317 --      proto_top_dir will be /...stuff.../ghc/compiler
318 --      Set TopDir to /...stuff..., which is the root of the build tree
319 --
320 -- This is very gruesome indeed
321
322 findTopDir :: Maybe String   -- Maybe TopDir path (without the '-B' prefix).
323            -> IO (Bool,      -- True <=> am installed, False <=> in-place
324                   String)    -- TopDir (in Unix format '/' separated)
325
326 findTopDir mbMinusB
327   = do { top_dir <- get_proto
328         -- Discover whether we're running in a build tree or in an installation,
329         -- by looking for a file we use for that purpose
330        ; am_inplace <- doesFileExist (top_dir </> "inplace")
331
332        ; return (not am_inplace, top_dir)
333        }
334   where
335     -- get_proto returns a Unix-format path (relying on getBaseDir to do so too)
336     get_proto = case mbMinusB of
337                   Just minusb -> return (normalise minusb)
338                   Nothing
339                       -> do maybe_exec_dir <- getBaseDir -- Get directory of executable
340                             case maybe_exec_dir of       -- (only works on Windows;
341                                                          --  returns Nothing on Unix)
342                               Nothing  -> throwDyn (InstallationError "missing -B<dir> option")
343                               Just dir -> return dir
344 \end{code}
345
346
347 %************************************************************************
348 %*                                                                      *
349 \subsection{Running an external program}
350 %*                                                                      *
351 %************************************************************************
352
353
354 \begin{code}
355 runUnlit :: DynFlags -> [Option] -> IO ()
356 runUnlit dflags args = do
357   let p = pgm_L dflags
358   runSomething dflags "Literate pre-processor" p args
359
360 runCpp :: DynFlags -> [Option] -> IO ()
361 runCpp dflags args =   do
362   let (p,args0) = pgm_P dflags
363       args1 = args0 ++ args
364   mb_env <- getGccEnv args1
365   runSomethingFiltered dflags id  "C pre-processor" p args1 mb_env
366
367 runPp :: DynFlags -> [Option] -> IO ()
368 runPp dflags args =   do
369   let p = pgm_F dflags
370   runSomething dflags "Haskell pre-processor" p args
371
372 runCc :: DynFlags -> [Option] -> IO ()
373 runCc dflags args =   do
374   let (p,args0) = pgm_c dflags
375       args1 = args0 ++ args
376   mb_env <- getGccEnv args1
377   runSomethingFiltered dflags cc_filter "C Compiler" p args1 mb_env
378  where
379   -- discard some harmless warnings from gcc that we can't turn off
380   cc_filter = unlines . doFilter . lines
381
382   {-
383   gcc gives warnings in chunks like so:
384       In file included from /foo/bar/baz.h:11,
385                        from /foo/bar/baz2.h:22,
386                        from wibble.c:33:
387       /foo/flibble:14: global register variable ...
388       /foo/flibble:15: warning: call-clobbered r...
389   We break it up into its chunks, remove any call-clobbered register
390   warnings from each chunk, and then delete any chunks that we have
391   emptied of warnings.
392   -}
393   doFilter = unChunkWarnings . filterWarnings . chunkWarnings []
394   -- We can't assume that the output will start with an "In file inc..."
395   -- line, so we start off expecting a list of warnings rather than a
396   -- location stack.
397   chunkWarnings :: [String] -- The location stack to use for the next
398                             -- list of warnings
399                 -> [String] -- The remaining lines to look at
400                 -> [([String], [String])]
401   chunkWarnings loc_stack [] = [(loc_stack, [])]
402   chunkWarnings loc_stack xs
403       = case break loc_stack_start xs of
404         (warnings, lss:xs') ->
405             case span loc_start_continuation xs' of
406             (lsc, xs'') ->
407                 (loc_stack, warnings) : chunkWarnings (lss : lsc) xs''
408         _ -> [(loc_stack, xs)]
409
410   filterWarnings :: [([String], [String])] -> [([String], [String])]
411   filterWarnings [] = []
412   -- If the warnings are already empty then we are probably doing
413   -- something wrong, so don't delete anything
414   filterWarnings ((xs, []) : zs) = (xs, []) : filterWarnings zs
415   filterWarnings ((xs, ys) : zs) = case filter wantedWarning ys of
416                                        [] -> filterWarnings zs
417                                        ys' -> (xs, ys') : filterWarnings zs
418
419   unChunkWarnings :: [([String], [String])] -> [String]
420   unChunkWarnings [] = []
421   unChunkWarnings ((xs, ys) : zs) = xs ++ ys ++ unChunkWarnings zs
422
423   loc_stack_start        s = "In file included from " `isPrefixOf` s
424   loc_start_continuation s = "                 from " `isPrefixOf` s
425   wantedWarning w
426    | "warning: call-clobbered register used" `isContainedIn` w = False
427    | otherwise = True
428
429 isContainedIn :: String -> String -> Bool
430 xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
431
432 -- If the -B<dir> option is set, add <dir> to PATH.  This works around
433 -- a bug in gcc on Windows Vista where it can't find its auxiliary
434 -- binaries (see bug #1110).
435 getGccEnv :: [Option] -> IO (Maybe [(String,String)])
436 getGccEnv opts =
437   if null b_dirs
438      then return Nothing
439      else do env <- getEnvironment
440              return (Just (map mangle_path env))
441  where
442   (b_dirs, _) = partitionWith get_b_opt opts
443
444   get_b_opt (Option ('-':'B':dir)) = Left dir
445   get_b_opt other = Right other
446
447   mangle_path (path,paths) | map toUpper path == "PATH"
448         = (path, '\"' : head b_dirs ++ "\";" ++ paths)
449   mangle_path other = other
450
451 runMangle :: DynFlags -> [Option] -> IO ()
452 runMangle dflags args = do
453   let (p,args0) = pgm_m dflags
454   runSomething dflags "Mangler" p (args0++args)
455
456 runSplit :: DynFlags -> [Option] -> IO ()
457 runSplit dflags args = do
458   let (p,args0) = pgm_s dflags
459   runSomething dflags "Splitter" p (args0++args)
460
461 runAs :: DynFlags -> [Option] -> IO ()
462 runAs dflags args = do
463   let (p,args0) = pgm_a dflags
464       args1 = args0 ++ args
465   mb_env <- getGccEnv args1
466   runSomethingFiltered dflags id "Assembler" p args1 mb_env
467
468 runLink :: DynFlags -> [Option] -> IO ()
469 runLink dflags args = do
470   let (p,args0) = pgm_l dflags
471       args1 = args0 ++ args
472   mb_env <- getGccEnv args1
473   runSomethingFiltered dflags id "Linker" p args1 mb_env
474
475 runMkDLL :: DynFlags -> [Option] -> IO ()
476 runMkDLL dflags args = do
477   let (p,args0) = pgm_dll dflags
478       args1 = args0 ++ args
479   mb_env <- getGccEnv (args0++args)
480   runSomethingFiltered dflags id "Make DLL" p args1 mb_env
481
482 runWindres :: DynFlags -> [Option] -> IO ()
483 runWindres dflags args = do
484   let (gcc,gcc_args) = pgm_c dflags
485       windres        = pgm_windres dflags
486   mb_env <- getGccEnv gcc_args
487   runSomethingFiltered dflags id "Windres" windres
488         -- we must tell windres where to find gcc: it might not be on PATH
489         (Option ("--preprocessor=" ++
490                  unwords (map quote (gcc : map showOpt gcc_args ++
491                                      ["-E", "-xc", "-DRC_INVOKED"])))
492         -- -- use-temp-file is required for windres to interpret the
493         -- quoting in the preprocessor arg above correctly.  Without
494         -- this, windres calls the preprocessor with popen, which gets
495         -- the quoting wrong (discovered by experimentation and
496         -- reading the windres sources).  See #1828.
497         : Option "--use-temp-file"
498         : args)
499         -- we must use the PATH workaround here too, since windres invokes gcc
500         mb_env
501   where
502         quote x = '\"' : x ++ "\""
503
504 touch :: DynFlags -> String -> String -> IO ()
505 touch dflags purpose arg =
506   runSomething dflags purpose (pgm_T dflags) [FileOption "" arg]
507
508 copy :: DynFlags -> String -> FilePath -> FilePath -> IO ()
509 copy dflags purpose from to = copyWithHeader dflags purpose Nothing from to
510
511 copyWithHeader :: DynFlags -> String -> Maybe String -> FilePath -> FilePath
512                -> IO ()
513 copyWithHeader dflags purpose maybe_header from to = do
514   showPass dflags purpose
515
516   h <- openFile to WriteMode
517   ls <- readFile from -- inefficient, but it'll do for now.
518                       -- ToDo: speed up via slurping.
519   maybe (return ()) (hPutStr h) maybe_header
520   hPutStr h ls
521   hClose h
522
523 getExtraViaCOpts :: DynFlags -> IO [String]
524 getExtraViaCOpts dflags = do
525   f <- readFile (topDir dflags </> "extra-gcc-opts")
526   return (words f)
527 \end{code}
528
529 %************************************************************************
530 %*                                                                      *
531 \subsection{Managing temporary files
532 %*                                                                      *
533 %************************************************************************
534
535 \begin{code}
536 GLOBAL_VAR(v_FilesToClean, [],               [String] )
537 GLOBAL_VAR(v_DirsToClean, emptyFM, FiniteMap FilePath FilePath )
538 \end{code}
539
540 \begin{code}
541 cleanTempDirs :: DynFlags -> IO ()
542 cleanTempDirs dflags
543    = unless (dopt Opt_KeepTmpFiles dflags)
544    $ do ds <- readIORef v_DirsToClean
545         removeTmpDirs dflags (eltsFM ds)
546         writeIORef v_DirsToClean emptyFM
547
548 cleanTempFiles :: DynFlags -> IO ()
549 cleanTempFiles dflags
550    = unless (dopt Opt_KeepTmpFiles dflags)
551    $ do fs <- readIORef v_FilesToClean
552         removeTmpFiles dflags fs
553         writeIORef v_FilesToClean []
554
555 cleanTempFilesExcept :: DynFlags -> [FilePath] -> IO ()
556 cleanTempFilesExcept dflags dont_delete
557    = unless (dopt Opt_KeepTmpFiles dflags)
558    $ do files <- readIORef v_FilesToClean
559         let (to_keep, to_delete) = partition (`elem` dont_delete) files
560         removeTmpFiles dflags to_delete
561         writeIORef v_FilesToClean to_keep
562
563
564 -- find a temporary name that doesn't already exist.
565 newTempName :: DynFlags -> Suffix -> IO FilePath
566 newTempName dflags extn
567   = do d <- getTempDir dflags
568        x <- getProcessID
569        findTempName (d ++ "/ghc" ++ show x ++ "_") 0
570   where
571     findTempName :: FilePath -> Integer -> IO FilePath
572     findTempName prefix x
573       = do let filename = (prefix ++ show x) <.> extn
574            b  <- doesFileExist filename
575            if b then findTempName prefix (x+1)
576                 else do consIORef v_FilesToClean filename -- clean it up later
577                         return filename
578
579 -- return our temporary directory within tmp_dir, creating one if we
580 -- don't have one yet
581 getTempDir :: DynFlags -> IO FilePath
582 getTempDir dflags@(DynFlags{tmpDir=tmp_dir})
583   = do mapping <- readIORef v_DirsToClean
584        case lookupFM mapping tmp_dir of
585            Nothing ->
586                do x <- getProcessID
587                   let prefix = tmp_dir ++ "/ghc" ++ show x ++ "_"
588                   let
589                       mkTempDir :: Integer -> IO FilePath
590                       mkTempDir x
591                        = let dirname = prefix ++ show x
592                          in do createDirectory dirname
593                                let mapping' = addToFM mapping tmp_dir dirname
594                                writeIORef v_DirsToClean mapping'
595                                debugTraceMsg dflags 2 (ptext (sLit "Created temporary directory:") <+> text dirname)
596                                return dirname
597                             `IO.catch` \e ->
598                                     if isAlreadyExistsError e
599                                     then mkTempDir (x+1)
600                                     else ioError e
601                   mkTempDir 0
602            Just d -> return d
603
604 addFilesToClean :: [FilePath] -> IO ()
605 -- May include wildcards [used by DriverPipeline.run_phase SplitMangle]
606 addFilesToClean files = mapM_ (consIORef v_FilesToClean) files
607
608 removeTmpDirs :: DynFlags -> [FilePath] -> IO ()
609 removeTmpDirs dflags ds
610   = traceCmd dflags "Deleting temp dirs"
611              ("Deleting: " ++ unwords ds)
612              (mapM_ (removeWith dflags removeDirectory) ds)
613
614 removeTmpFiles :: DynFlags -> [FilePath] -> IO ()
615 removeTmpFiles dflags fs
616   = warnNon $
617     traceCmd dflags "Deleting temp files"
618              ("Deleting: " ++ unwords deletees)
619              (mapM_ (removeWith dflags removeFile) deletees)
620   where
621      -- Flat out refuse to delete files that are likely to be source input
622      -- files (is there a worse bug than having a compiler delete your source
623      -- files?)
624      --
625      -- Deleting source files is a sign of a bug elsewhere, so prominently flag
626      -- the condition.
627     warnNon act
628      | null non_deletees = act
629      | otherwise         = do
630         putMsg dflags (text "WARNING - NOT deleting source files:" <+> hsep (map text non_deletees))
631         act
632
633     (non_deletees, deletees) = partition isHaskellUserSrcFilename fs
634
635 removeWith :: DynFlags -> (FilePath -> IO ()) -> FilePath -> IO ()
636 removeWith dflags remover f = remover f `IO.catch`
637   (\e ->
638    let msg = if isDoesNotExistError e
639              then ptext (sLit "Warning: deleting non-existent") <+> text f
640              else ptext (sLit "Warning: exception raised when deleting")
641                                             <+> text f <> colon
642                $$ text (show e)
643    in debugTraceMsg dflags 2 msg
644   )
645
646 -----------------------------------------------------------------------------
647 -- Running an external program
648
649 runSomething :: DynFlags
650              -> String          -- For -v message
651              -> String          -- Command name (possibly a full path)
652                                 --      assumed already dos-ified
653              -> [Option]        -- Arguments
654                                 --      runSomething will dos-ify them
655              -> IO ()
656
657 runSomething dflags phase_name pgm args =
658   runSomethingFiltered dflags id phase_name pgm args Nothing
659
660 runSomethingFiltered
661   :: DynFlags -> (String->String) -> String -> String -> [Option]
662   -> Maybe [(String,String)] -> IO ()
663
664 runSomethingFiltered dflags filter_fn phase_name pgm args mb_env = do
665   let real_args = filter notNull (map showOpt args)
666   traceCmd dflags phase_name (unwords (pgm:real_args)) $ do
667   (exit_code, doesn'tExist) <-
668      IO.catch (do
669          rc <- builderMainLoop dflags filter_fn pgm real_args mb_env
670          case rc of
671            ExitSuccess{} -> return (rc, False)
672            ExitFailure n
673              -- rawSystem returns (ExitFailure 127) if the exec failed for any
674              -- reason (eg. the program doesn't exist).  This is the only clue
675              -- we have, but we need to report something to the user because in
676              -- the case of a missing program there will otherwise be no output
677              -- at all.
678             | n == 127  -> return (rc, True)
679             | otherwise -> return (rc, False))
680                 -- Should 'rawSystem' generate an IO exception indicating that
681                 -- 'pgm' couldn't be run rather than a funky return code, catch
682                 -- this here (the win32 version does this, but it doesn't hurt
683                 -- to test for this in general.)
684               (\ err ->
685                 if IO.isDoesNotExistError err
686                  then return (ExitFailure 1, True)
687                  else IO.ioError err)
688   case (doesn'tExist, exit_code) of
689      (True, _)        -> throwDyn (InstallationError ("could not execute: " ++ pgm))
690      (_, ExitSuccess) -> return ()
691      _                -> throwDyn (PhaseFailed phase_name exit_code)
692
693 builderMainLoop :: DynFlags -> (String -> String) -> FilePath
694                 -> [String] -> Maybe [(String, String)]
695                 -> IO ExitCode
696 builderMainLoop dflags filter_fn pgm real_args mb_env = do
697   chan <- newChan
698   (hStdIn, hStdOut, hStdErr, hProcess) <- runInteractiveProcess pgm real_args Nothing mb_env
699
700   -- and run a loop piping the output from the compiler to the log_action in DynFlags
701   hSetBuffering hStdOut LineBuffering
702   hSetBuffering hStdErr LineBuffering
703   forkIO (readerProc chan hStdOut filter_fn)
704   forkIO (readerProc chan hStdErr filter_fn)
705   -- we don't want to finish until 2 streams have been completed
706   -- (stdout and stderr)
707   -- nor until 1 exit code has been retrieved.
708   rc <- loop chan hProcess (2::Integer) (1::Integer) ExitSuccess
709   -- after that, we're done here.
710   hClose hStdIn
711   hClose hStdOut
712   hClose hStdErr
713   return rc
714   where
715     -- status starts at zero, and increments each time either
716     -- a reader process gets EOF, or the build proc exits.  We wait
717     -- for all of these to happen (status==3).
718     -- ToDo: we should really have a contingency plan in case any of
719     -- the threads dies, such as a timeout.
720     loop _    _        0 0 exitcode = return exitcode
721     loop chan hProcess t p exitcode = do
722       mb_code <- if p > 0
723                    then getProcessExitCode hProcess
724                    else return Nothing
725       case mb_code of
726         Just code -> loop chan hProcess t (p-1) code
727         Nothing
728           | t > 0 -> do
729               msg <- readChan chan
730               case msg of
731                 BuildMsg msg -> do
732                   log_action dflags SevInfo noSrcSpan defaultUserStyle msg
733                   loop chan hProcess t p exitcode
734                 BuildError loc msg -> do
735                   log_action dflags SevError (mkSrcSpan loc loc) defaultUserStyle msg
736                   loop chan hProcess t p exitcode
737                 EOF ->
738                   loop chan hProcess (t-1) p exitcode
739           | otherwise -> loop chan hProcess t p exitcode
740
741 readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO ()
742 readerProc chan hdl filter_fn =
743     (do str <- hGetContents hdl
744         loop (linesPlatform (filter_fn str)) Nothing)
745     `finally`
746        writeChan chan EOF
747         -- ToDo: check errors more carefully
748         -- ToDo: in the future, the filter should be implemented as
749         -- a stream transformer.
750     where
751         loop []     Nothing    = return ()
752         loop []     (Just err) = writeChan chan err
753         loop (l:ls) in_err     =
754                 case in_err of
755                   Just err@(BuildError srcLoc msg)
756                     | leading_whitespace l -> do
757                         loop ls (Just (BuildError srcLoc (msg $$ text l)))
758                     | otherwise -> do
759                         writeChan chan err
760                         checkError l ls
761                   Nothing -> do
762                         checkError l ls
763                   _ -> panic "readerProc/loop"
764
765         checkError l ls
766            = case parseError l of
767                 Nothing -> do
768                     writeChan chan (BuildMsg (text l))
769                     loop ls Nothing
770                 Just (file, lineNum, colNum, msg) -> do
771                     let srcLoc = mkSrcLoc (mkFastString file) lineNum colNum
772                     loop ls (Just (BuildError srcLoc (text msg)))
773
774         leading_whitespace []    = False
775         leading_whitespace (x:_) = isSpace x
776
777 parseError :: String -> Maybe (String, Int, Int, String)
778 parseError s0 = case breakColon s0 of
779                 Just (filename, s1) ->
780                     case breakIntColon s1 of
781                     Just (lineNum, s2) ->
782                         case breakIntColon s2 of
783                         Just (columnNum, s3) ->
784                             Just (filename, lineNum, columnNum, s3)
785                         Nothing ->
786                             Just (filename, lineNum, 0, s2)
787                     Nothing -> Nothing
788                 Nothing -> Nothing
789
790 breakColon :: String -> Maybe (String, String)
791 breakColon xs = case break (':' ==) xs of
792                     (ys, _:zs) -> Just (ys, zs)
793                     _ -> Nothing
794
795 breakIntColon :: String -> Maybe (Int, String)
796 breakIntColon xs = case break (':' ==) xs of
797                        (ys, _:zs)
798                         | not (null ys) && all isAscii ys && all isDigit ys ->
799                            Just (read ys, zs)
800                        _ -> Nothing
801
802 data BuildMessage
803   = BuildMsg   !SDoc
804   | BuildError !SrcLoc !SDoc
805   | EOF
806
807 showOpt :: Option -> String
808 showOpt (FileOption pre f) = pre ++ f
809 showOpt (Option s)  = s
810
811 traceCmd :: DynFlags -> String -> String -> IO () -> IO ()
812 -- a) trace the command (at two levels of verbosity)
813 -- b) don't do it at all if dry-run is set
814 traceCmd dflags phase_name cmd_line action
815  = do   { let verb = verbosity dflags
816         ; showPass dflags phase_name
817         ; debugTraceMsg dflags 3 (text cmd_line)
818         ; hFlush stderr
819
820            -- Test for -n flag
821         ; unless (dopt Opt_DryRun dflags) $ do {
822
823            -- And run it!
824         ; action `IO.catch` handle_exn verb
825         }}
826   where
827     handle_exn _verb exn = do { debugTraceMsg dflags 2 (char '\n')
828                               ; debugTraceMsg dflags 2 (ptext (sLit "Failed:") <+> text cmd_line <+> text (show exn))
829                               ; throwDyn (PhaseFailed phase_name (ExitFailure 1)) }
830 \end{code}
831
832 %************************************************************************
833 %*                                                                      *
834 \subsection{Support code}
835 %*                                                                      *
836 %************************************************************************
837
838 \begin{code}
839 -----------------------------------------------------------------------------
840 -- Define       getBaseDir     :: IO (Maybe String)
841
842 getBaseDir :: IO (Maybe String)
843 #if defined(mingw32_HOST_OS)
844 -- Assuming we are running ghc, accessed by path  $()/bin/ghc.exe,
845 -- return the path $(stuff).  Note that we drop the "bin/" directory too.
846 getBaseDir = do let len = (2048::Int) -- plenty, PATH_MAX is 512 under Win32.
847                 buf <- mallocArray len
848                 ret <- getModuleFileName nullPtr buf len
849                 if ret == 0 then free buf >> return Nothing
850                             else do s <- peekCString buf
851                                     free buf
852                                     return (Just (rootDir s))
853   where
854     rootDir s = case splitFileName $ normalise s of
855                 (d, "ghc.exe") ->
856                     case splitFileName $ takeDirectory d of
857                     (d', "bin") -> takeDirectory d'
858                     _ -> panic ("Expected \"bin\" in " ++ show s)
859                 _ -> panic ("Expected \"ghc.exe\" in " ++ show s)
860
861 foreign import stdcall unsafe "GetModuleFileNameA"
862   getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
863 #else
864 getBaseDir = return Nothing
865 #endif
866
867 #ifdef mingw32_HOST_OS
868 foreign import ccall unsafe "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
869 #else
870 getProcessID :: IO Int
871 getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral
872 #endif
873
874 -- Divvy up text stream into lines, taking platform dependent
875 -- line termination into account.
876 linesPlatform :: String -> [String]
877 #if !defined(mingw32_HOST_OS)
878 linesPlatform ls = lines ls
879 #else
880 linesPlatform "" = []
881 linesPlatform xs =
882   case lineBreak xs of
883     (as,xs1) -> as : linesPlatform xs1
884   where
885    lineBreak "" = ("","")
886    lineBreak ('\r':'\n':xs) = ([],xs)
887    lineBreak ('\n':xs) = ([],xs)
888    lineBreak (x:xs) = let (as,bs) = lineBreak xs in (x:as,bs)
889
890 #endif
891
892 \end{code}