[project @ 2003-07-17 08:59:03 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / SysTools.lhs
index 3297a09..576761b 100644 (file)
@@ -65,6 +65,7 @@ module SysTools (
 #include "HsVersions.h"
 
 import DriverUtil
+import DriverPhases     ( haskellish_user_src_file )
 import Config
 import Outputable
 import Panic           ( progName, GhcException(..) )
@@ -81,25 +82,21 @@ import IO           ( try, catch,
                          openFile, hPutChar, hPutStrLn, hPutStr, hClose, hFlush, IOMode(..),
                          stderr )
 import Directory       ( doesFileExist, removeFile )
-import List             ( intersperse )
+import List             ( intersperse, partition )
 
 #include "../includes/config.h"
 
 -- GHC <= 4.08 didn't have rawSystem, and runs into problems with long command
 -- lines on mingw32, so we disallow it now.
-#if defined(mingw32_HOST_OS) && (__GLASGOW_HASKELL__ <= 408)
-#error GHC <= 4.08 is not supported for bootstrapping GHC on i386-unknown-mingw32
+#if __GLASGOW_HASKELL__ < 500
+#error GHC >= 5.00 is required for bootstrapping GHC
 #endif
 
 #ifndef mingw32_HOST_OS
 #if __GLASGOW_HASKELL__ > 504
 import qualified System.Posix.Internals
-import System.Posix.Process ( executeFile, getProcessStatus, forkProcess, ProcessStatus(..))
-import System.Posix.Signals ( installHandler, sigCHLD, sigCONT, Handler(..) )
 #else
 import qualified Posix
-import Posix ( executeFile, getProcessStatus, forkProcess, ProcessStatus(..), installHandler,
-               sigCHLD, sigCONT, Handler(..) )
 #endif
 #else /* Must be Win32 */
 import List            ( isPrefixOf )
@@ -108,12 +105,11 @@ import Foreign
 import CString         ( CString, peekCString )
 #endif
 
-#ifdef mingw32_HOST_OS
-#if __GLASGOW_HASKELL__ > 504
-import System.Cmd       ( rawSystem )
+#if __GLASGOW_HASKELL__ < 601
+import Foreign         ( withMany, withArray0, nullPtr, Ptr )
+import CForeign                ( CString, withCString, throwErrnoIfMinus1 )
 #else
-import SystemExts       ( rawSystem )
-#endif
+import System.Cmd      ( rawSystem )
 #endif
 \end{code}
 
@@ -283,30 +279,21 @@ initSysTools minusB_args
          -- On Win32, consult GetTempPath() for a temp dir.
          --  => it first tries TMP, TEMP, then finally the
          --   Windows directory(!). The directory is in short-path
-         --   form and *does* have a trailing backslash.
+         --   form.
        ; IO.try (do
                let len = (2048::Int)
                buf  <- mallocArray len
                ret  <- getTempPath len buf
                tdir <-
                  if ret == 0 then do
-                     -- failed, consult TEMP.
+                     -- failed, consult TMPDIR.
                     free buf
-                    getEnv "TMP"
+                    getEnv "TMPDIR"
                   else do
                     s <- peekCString buf
                     free buf
                     return s
-               let
-                 -- strip the trailing backslash (awful, but 
-                 -- we only do this once).
-                 tmpdir =
-                   case last tdir of
-                     '/'  -> init tdir
-                     '\\' -> init tdir
-                     _   -> tdir
-               setTmpDir tmpdir
-               return ())
+               setTmpDir tdir)
 #endif
 
        -- Check that the package config exists
@@ -632,7 +619,36 @@ GLOBAL_VAR(v_TmpDir,       cDEFAULT_TMPDIR,  String   )
 \end{code}
 
 \begin{code}
-setTmpDir dir = writeIORef v_TmpDir dir
+setTmpDir dir = writeIORef v_TmpDir (canonicalise dir)
+    where
+#if !defined(mingw32_HOST_OS)
+     canonicalise p = normalisePath p
+#else
+       -- Canonicalisation of temp path under win32 is a bit more
+       -- involved: (a) strip trailing slash, 
+       --           (b) normalise slashes
+       --           (c) just in case, if there is a prefix /cygdrive/x/, change to x:
+       -- 
+     canonicalise path = normalisePath (xltCygdrive (removeTrailingSlash path))
+
+        -- if we're operating under cygwin, and TMP/TEMP is of
+       -- the form "/cygdrive/drive/path", translate this to
+       -- "drive:/path" (as GHC isn't a cygwin app and doesn't
+       -- understand /cygdrive paths.)
+     xltCygdrive path
+      | "/cygdrive/" `isPrefixOf` path = 
+         case drop (length "/cygdrive/") path of
+           drive:xs@('/':_) -> drive:':':xs
+           _ -> path
+      | otherwise = path
+
+        -- strip the trailing backslash (awful, but we only do this once).
+     removeTrailingSlash path = 
+       case last path of
+         '/'  -> init path
+         '\\' -> init path
+         _    -> path
+#endif
 
 cleanTempFiles :: Int -> IO ()
 cleanTempFiles verb = do fs <- readIORef v_FilesToClean
@@ -666,10 +682,25 @@ addFilesToClean files = mapM_ (add v_FilesToClean) files
 
 removeTmpFiles :: Int -> [FilePath] -> IO ()
 removeTmpFiles verb fs
-  = traceCmd "Deleting temp files" 
-            ("Deleting: " ++ unwords fs)
-            (mapM_ rm fs)
+  = warnNon $
+    traceCmd "Deleting temp files" 
+            ("Deleting: " ++ unwords deletees)
+            (mapM_ rm deletees)
   where
+     -- Flat out refuse to delete files that are likely to be source input
+     -- files (is there a worse bug than having a compiler delete your source
+     -- files?)
+     -- 
+     -- Deleting source files is a sign of a bug elsewhere, so prominently flag
+     -- the condition.
+    warnNon act
+     | null non_deletees = act
+     | otherwise         = do
+        hPutStrLn stderr ("WARNING - NOT deleting source files: " ++ unwords non_deletees)
+       act
+
+    (non_deletees, deletees) = partition haskellish_user_src_file fs
+
     rm f = removeFile f `IO.catch` 
                (\_ignored -> 
                    when (verb >= 2) $
@@ -701,51 +732,13 @@ runSomething :: String            -- For -v message
                                --      runSomething will dos-ify them
             -> IO ()
 
-runSomething phase_name pgm args
- = traceCmd phase_name (concat (intersperse " " (pgm:quoteargs))) $
-   do
-#ifdef mingw32_HOST_OS
-          let showOptions :: [Option] -> String
-              showOptions ls = unwords (map (quote . showOpt) ls)
-
-              quote :: String -> String
-              quote "" = ""
-              quote s  = "\"" ++ escapeDoubleQuotes s ++ "\""
-
-              escapeDoubleQuotes :: String -> String
-              escapeDoubleQuotes ""            = ""
-              escapeDoubleQuotes ('\\':'"':cs) = '\\':'"':escapeDoubleQuotes cs
-              escapeDoubleQuotes (     '"':cs) = '\\':'"':escapeDoubleQuotes cs
-              escapeDoubleQuotes (c       :cs) = c       :escapeDoubleQuotes cs
-
-          -- The pgm is already in native format (appropriate dir separators)
-          exit_code <- rawSystem (pgm ++ ' ':showOptions args)
-#else
-          mpid <- forkProcess
-          exit_code <- case mpid of
-            Nothing -> do -- Child
-             executeFile pgm True quoteargs Nothing
-              exitWith (ExitFailure 127)
-             -- NOT REACHED
-              return ExitSuccess
-            Just child -> do -- Parent
-#if __GLASGOW_HASKELL__ <= 504
-              -- avoid interaction with broken getProcessStatus-FFI:
-              oldHandler <- installHandler sigCONT Ignore Nothing
-#endif
-              Just (Exited res) <- getProcessStatus True False child
-#if __GLASGOW_HASKELL__ <= 504
-              -- restore handler
-              installHandler sigCONT oldHandler Nothing
-#endif
-
-              return res
-#endif
-         when (exit_code /= ExitSuccess) $
-            throwDyn (PhaseFailed phase_name exit_code)
-          return ()    
-  where
-    quoteargs = filter (not . null) (map showOpt args)
+runSomething phase_name pgm args = do
+  let real_args = filter notNull (map showOpt args)
+  traceCmd phase_name (concat (intersperse " " (pgm:real_args))) $ do
+  exit_code <- rawSystem pgm real_args
+  if (exit_code /= ExitSuccess)
+       then throwDyn (PhaseFailed phase_name exit_code)
+       else return ()
 
 traceCmd :: String -> String -> IO () -> IO ()
 -- a) trace the command (at two levels of verbosity)
@@ -767,6 +760,57 @@ traceCmd phase_name cmd_line action
     handle_exn verb exn = do { when (verb >= 2) (hPutStr   stderr "\n")
                             ; when (verb >= 3) (hPutStrLn stderr ("Failed: " ++ cmd_line ++ (show exn)))
                             ; throwDyn (PhaseFailed phase_name (ExitFailure 1)) }
+
+-- -----------------------------------------------------------------------------
+-- rawSystem: run an external command
+
+#if __GLASGOW_HASKELL__ < 601
+
+-- This code is copied from System.Cmd on GHC 6.1.
+
+rawSystem :: FilePath -> [String] -> IO ExitCode
+
+#ifndef mingw32_TARGET_OS
+
+rawSystem cmd args =
+  withCString cmd $ \pcmd ->
+    withMany withCString (cmd:args) $ \cstrs ->
+      withArray0 nullPtr cstrs $ \arr -> do
+       status <- throwErrnoIfMinus1 "rawSystem" (c_rawSystem pcmd arr)
+        case status of
+            0  -> return ExitSuccess
+            n  -> return (ExitFailure n)
+
+foreign import ccall "rawSystem" unsafe
+  c_rawSystem :: CString -> Ptr CString -> IO Int
+
+#else
+
+-- On Windows, the command line is passed to the operating system as
+-- a single string.  Command-line parsing is done by the executable
+-- itself.
+rawSystem cmd args = do
+  let cmdline = {-translate-} cmd ++ concat (map ((' ':) . translate) args)
+       -- Urk, don't quote/escape the command name on Windows, because the
+       -- compiler is exceedingly naughty and sometimes uses 'perl "..."' 
+       -- as the command name.
+  withCString cmdline $ \pcmdline -> do
+    status <- throwErrnoIfMinus1 "rawSystem" (c_rawSystem pcmdline)
+    case status of
+       0  -> return ExitSuccess
+       n  -> return (ExitFailure n)
+
+translate :: String -> String
+translate str = '"' : foldr escape "\"" str
+  where escape '"'  str = '\\' : '"'  : str
+       escape '\\' str = '\\' : '\\' : str
+       escape c    str = c : str
+
+foreign import ccall "rawSystem" unsafe
+  c_rawSystem :: CString -> IO Int
+
+#endif
+#endif
 \end{code}
 
 
@@ -789,12 +833,8 @@ interpreted a command line 'foo\baz' as 'foobaz'.
 -----------------------------------------------------------------------------
 -- Convert filepath into platform / MSDOS form.
 
--- platformPath does two things
--- a) change '/' to '\'
--- b) remove initial '/cygdrive/'
-
 normalisePath :: String -> String
--- Just change '\' to '/'
+-- Just changes '\' to '/'
 
 pgmPath :: String              -- Directory string in Unix format
        -> String               -- Program name with no directory separators