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