windres also needs the PATH workaround, because it runs gcc
[ghc-hetmet.git] / compiler / main / SysTools.lhs
index a4224e9..2d4333c 100644 (file)
@@ -17,11 +17,13 @@ module SysTools (
        runMangle, runSplit,     -- [Option] -> IO ()
        runAs, runLink,          -- [Option] -> IO ()
        runMkDLL,
+        runWindres,
 
        touch,                  -- String -> String -> IO ()
        copy,
         copyWithHeader,
        normalisePath,          -- FilePath -> FilePath
+        getExtraViaCOpts,
        
        -- Temporary-file management
        setTmpDir,
@@ -57,11 +59,7 @@ import Data.Maybe
 import Data.List
 
 #ifndef mingw32_HOST_OS
-#if __GLASGOW_HASKELL__ > 504
 import qualified System.Posix.Internals
-#else
-import qualified Posix
-#endif
 #else /* Must be Win32 */
 import Foreign
 import CString         ( CString, peekCString )
@@ -75,7 +73,6 @@ import GHC.IOBase       ( IOErrorType(..) )
 #else
 import System.Process  ( runInteractiveProcess, getProcessExitCode )
 import Control.Concurrent( forkIO, newChan, readChan, writeChan )
-import Data.Char        ( isSpace )
 import FastString       ( mkFastString )
 import SrcLoc           ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan )
 #endif
@@ -200,6 +197,10 @@ initSysTools mbMinusB dflags
                | am_installed = installed_bin cGHC_MANGLER_PGM
                | otherwise    = inplace cGHC_MANGLER_DIR_REL cGHC_MANGLER_PGM
 
+              windres_path
+               | am_installed = installed_bin "bin/windres"
+               | otherwise    = "windres"
+
        ; let dflags0 = defaultDynFlags
 #ifndef mingw32_HOST_OS
        -- check whether TMPDIR is set in the environment
@@ -330,7 +331,8 @@ initSysTools mbMinusB dflags
                        pgm_l   = (ld_prog,ld_args),
                        pgm_dll = (mkdll_prog,mkdll_args),
                         pgm_T   = touch_path,
-                        pgm_sysman = top_dir ++ "/ghc/rts/parallel/SysMan"
+                        pgm_sysman = top_dir ++ "/ghc/rts/parallel/SysMan",
+                        pgm_windres = windres_path
                        -- Hans: this isn't right in general, but you can 
                        -- elaborate it in the same way as the others
                 }
@@ -474,7 +476,7 @@ xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
 getGccEnv :: [Option] -> IO (Maybe [(String,String)])
 getGccEnv opts = 
 #if __GLASGOW_HASKELL__ < 603
-  return (opts,Nothing)
+  return Nothing
 #else
   if null b_dirs
      then return Nothing
@@ -486,7 +488,8 @@ getGccEnv opts =
   get_b_opt (Option ('-':'B':dir)) = Left dir
   get_b_opt other = Right other  
 
-  mangle_path ("PATH",paths) = ("PATH", '\"' : head b_dirs ++ "\";" ++ paths)
+  mangle_path (path,paths) | map toUpper path == "PATH" 
+        = (path, '\"' : head b_dirs ++ "\";" ++ paths)
   mangle_path other = other
 #endif
 
@@ -510,7 +513,9 @@ runAs dflags args = do
 runLink :: DynFlags -> [Option] -> IO ()
 runLink dflags args = do 
   let (p,args0) = pgm_l dflags
-  runSomething dflags "Linker" p (args0++args)
+      args1 = args0 ++ args
+  mb_env <- getGccEnv args1
+  runSomethingFiltered dflags id "Linker" p args1 mb_env
 
 runMkDLL :: DynFlags -> [Option] -> IO ()
 runMkDLL dflags args = do
@@ -519,6 +524,20 @@ runMkDLL dflags args = do
   mb_env <- getGccEnv (args0++args)
   runSomethingFiltered dflags id "Make DLL" p args1 mb_env
 
+runWindres :: DynFlags -> [Option] -> IO ()
+runWindres dflags args = do
+  let (gcc,gcc_args) = pgm_c dflags
+      windres        = pgm_windres dflags
+  mb_env <- getGccEnv gcc_args
+  runSomethingFiltered dflags id "Windres" windres 
+        -- we must tell windres where to find gcc: it might not be on PATH
+        (Option ("--preprocessor=" ++ gcc ++ " " ++
+                                      unwords (map showOpt gcc_args) ++
+                 " -E -xc -DRC_INVOKED")
+         : args)
+        -- we must use the PATH workaround here too, since windres invokes gcc
+        mb_env
+
 touch :: DynFlags -> String -> String -> IO ()
 touch dflags purpose arg =
   runSomething dflags purpose (pgm_T dflags) [FileOption "" arg]
@@ -538,6 +557,10 @@ copyWithHeader dflags purpose maybe_header from to = do
   hPutStr h ls
   hClose h
 
+getExtraViaCOpts :: DynFlags -> IO [String]
+getExtraViaCOpts dflags = do
+  f <- readFile (topDir dflags `joinFileName` "extra-gcc-opts")
+  return (words f)
 \end{code}
 
 %************************************************************************
@@ -581,7 +604,8 @@ newTempName dflags extn
   = do d <- getTempDir dflags
        x <- getProcessID
        findTempName (d ++ "/ghc" ++ show x ++ "_") 0
-  where 
+  where
+    findTempName :: FilePath -> Integer -> IO FilePath
     findTempName prefix x
       = do let filename = (prefix ++ show x) `joinFileExt` extn
           b  <- doesFileExist filename
@@ -598,6 +622,8 @@ getTempDir dflags@(DynFlags{tmpDir=tmp_dir})
            Nothing ->
                do x <- getProcessID
                   let prefix = tmp_dir ++ "/ghc" ++ show x ++ "_"
+                  let
+                      mkTempDir :: Integer -> IO FilePath
                       mkTempDir x
                        = let dirname = prefix ++ show x
                          in do createDirectory dirname
@@ -721,7 +747,11 @@ builderMainLoop dflags filter_fn pgm real_args mb_env = do
   hSetBuffering hStdErr LineBuffering
   forkIO (readerProc chan hStdOut filter_fn)
   forkIO (readerProc chan hStdErr filter_fn)
-  rc <- loop chan hProcess 2 1 ExitSuccess
+  -- we don't want to finish until 2 streams have been completed
+  -- (stdout and stderr)
+  -- nor until 1 exit code has been retrieved.
+  rc <- loop chan hProcess (2::Integer) (1::Integer) ExitSuccess
+  -- after that, we're done here.
   hClose hStdIn
   hClose hStdOut
   hClose hStdErr
@@ -875,12 +905,9 @@ getBaseDir = return Nothing
 
 #ifdef mingw32_HOST_OS
 foreign import ccall unsafe "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
-#elif __GLASGOW_HASKELL__ > 504
-getProcessID :: IO Int
-getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral
 #else
 getProcessID :: IO Int
-getProcessID = Posix.getProcessID
+getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral
 #endif
 
 -- Divvy up text stream into lines, taking platform dependent