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