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