[project @ 2003-07-17 08:59:03 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / SysTools.lhs
index 71b7298..576761b 100644 (file)
@@ -42,7 +42,7 @@ module SysTools (
 
        touch,                  -- String -> String -> IO ()
        copy,                   -- String -> String -> String -> IO ()
-       unDosifyPath,           -- String -> String
+       normalisePath,          -- FilePath -> FilePath
        
        -- Temporary-file management
        setTmpDir,
@@ -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,18 +82,19 @@ import IO           ( try, catch,
                          openFile, hPutChar, hPutStrLn, hPutStr, hClose, hFlush, IOMode(..),
                          stderr )
 import Directory       ( doesFileExist, removeFile )
+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 GHC.Posix
+import qualified System.Posix.Internals
 #else
 import qualified Posix
 #endif
@@ -103,16 +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
-
-#else /* Not Win32 */
-
-import System          ( system )
+import System.Cmd      ( rawSystem )
 #endif
 \end{code}
 
@@ -190,7 +187,7 @@ All these pathnames are maintained IN THE NATIVE FORMAT OF THE HOST MACHINE.
 
 \begin{code}
 GLOBAL_VAR(v_Pgm_L,    error "pgm_L",   String)        -- unlit
-GLOBAL_VAR(v_Pgm_P,    error "pgm_P",   String)        -- cpp
+GLOBAL_VAR(v_Pgm_P,    error "pgm_P",   (String,[Option]))     -- cpp
 GLOBAL_VAR(v_Pgm_F,    error "pgm_F",   String)        -- pp
 GLOBAL_VAR(v_Pgm_c,    error "pgm_c",   String)        -- gcc
 GLOBAL_VAR(v_Pgm_m,    error "pgm_m",   String)        -- asm code mangler
@@ -282,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
@@ -374,7 +362,9 @@ initSysTools minusB_args
 #endif
 
        -- cpp is derived from gcc on all platforms
-        ; let cpp_path  = gcc_path ++ " -E " ++ cRAWCPP_FLAGS
+        -- HACK, see setPgmP below. We keep 'words' here to remember to fix
+        -- Config.hs one day.
+        ; let cpp_path  = (gcc_path, (Option "-E"):(map Option (words cRAWCPP_FLAGS)))
 
        -- For all systems, copy and remove are provided by the host
        -- system; architecture-specific stuff is done when building Config.hs
@@ -431,7 +421,9 @@ is used to override a particular program with a new one
 
 \begin{code}
 setPgmL = writeIORef v_Pgm_L
-setPgmP = writeIORef v_Pgm_P
+-- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
+-- Config.hs should really use Option.
+setPgmP arg = let (pgm:args) = words arg in writeIORef v_Pgm_P (pgm,map Option args)
 setPgmF = writeIORef v_Pgm_F
 setPgmc = writeIORef v_Pgm_c
 setPgmm = writeIORef v_Pgm_m
@@ -478,11 +470,11 @@ findTopDir minusbs
        ; return (am_installed, top_dir)
        }
   where
-    -- get_proto returns a Unix-format path (relying on getExecDir to do so too)
+    -- get_proto returns a Unix-format path (relying on getBaseDir to do so too)
     get_proto | notNull minusbs
-             = return (unDosifyPath (drop 2 (last minusbs)))   -- 2 for "-B"
+             = return (normalisePath (drop 2 (last minusbs)))  -- 2 for "-B"
              | otherwise          
-             = do { maybe_exec_dir <- getExecDir -- Get directory of executable
+             = do { maybe_exec_dir <- getBaseDir -- Get directory of executable
                   ; case maybe_exec_dir of       -- (only works on Windows; 
                                                  --  returns Nothing on Unix)
                        Nothing  -> throwDyn (InstallationError "missing -B<dir> option")
@@ -511,11 +503,9 @@ data Option
              String  -- the filepath/filename portion
  | Option     String
  
-showOptions :: [Option] -> String
-showOptions ls = unwords (map (quote.showOpt) ls)
- where
-   showOpt (FileOption pre f) = pre ++ dosifyPath f
-   showOpt (Option s)     = s
+showOpt (FileOption pre f) = pre ++ platformPath f
+showOpt (Option "") = ""
+showOpt (Option s)  = s
 
 \end{code}
 
@@ -533,8 +523,8 @@ runUnlit args = do p <- readIORef v_Pgm_L
                   runSomething "Literate pre-processor" p args
 
 runCpp :: [Option] -> IO ()
-runCpp args =   do p <- readIORef v_Pgm_P
-                  runSomething "C pre-processor" p args
+runCpp args =   do (p,baseArgs) <- readIORef v_Pgm_P
+                  runSomething "C pre-processor" p (baseArgs ++ args)
 
 runPp :: [Option] -> IO ()
 runPp args =   do p <- readIORef v_Pgm_F
@@ -629,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
@@ -663,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) $
@@ -698,22 +732,13 @@ runSomething :: String            -- For -v message
                                --      runSomething will dos-ify them
             -> IO ()
 
-runSomething phase_name pgm args
- = traceCmd phase_name cmd_line $
-   do   {
-#ifndef mingw32_HOST_OS
-         exit_code <- system cmd_line
-#else
-          exit_code <- rawSystem cmd_line
-#endif
-       ; if exit_code /= ExitSuccess
-         then throwDyn (PhaseFailed phase_name exit_code)
-         else return ()
-       }
-  where
-       -- The pgm is already in native format (appropriate dir separators)
-    cmd_line = pgm ++ ' ':showOptions args 
-                -- unwords (pgm : dosifyPaths (map quote 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)
@@ -733,8 +758,59 @@ traceCmd phase_name cmd_line action
        }}
   where
     handle_exn verb exn = do { when (verb >= 2) (hPutStr   stderr "\n")
-                            ; when (verb >= 3) (hPutStrLn stderr ("Failed: " ++ cmd_line))
+                            ; 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}
 
 
@@ -749,21 +825,16 @@ the last moment.  On Windows we dos-ify them just before passing them
 to the Windows command.
 
 The alternative, of using '/' consistently on Unix and '\' on Windows,
-proved quite awkward.  There were a lot more calls to dosifyPath,
+proved quite awkward.  There were a lot more calls to platformPath,
 and even on Windows we might invoke a unix-like utility (eg 'sh'), which
 interpreted a command line 'foo\baz' as 'foobaz'.
 
 \begin{code}
 -----------------------------------------------------------------------------
--- Convert filepath into MSDOS form.
-
-dosifyPaths :: [String] -> [String]
--- dosifyPaths does two things
--- a) change '/' to '\'
--- b) remove initial '/cygdrive/'
+-- Convert filepath into platform / MSDOS form.
 
-unDosifyPath :: String -> String
--- Just change '\' to '/'
+normalisePath :: String -> String
+-- Just changes '\' to '/'
 
 pgmPath :: String              -- Directory string in Unix format
        -> String               -- Program name with no directory separators
@@ -773,36 +844,20 @@ pgmPath :: String         -- Directory string in Unix format
 
 
 #if defined(mingw32_HOST_OS)
-
 --------------------- Windows version ------------------
-dosifyPaths xs = map dosifyPath xs
-
-unDosifyPath xs = subst '\\' '/' xs
-
-pgmPath dir pgm = dosifyPath dir ++ '\\' : pgm
+normalisePath xs = subst '\\' '/' xs
+platformPath p   = subst '/' '\\' p
+pgmPath dir pgm  = platformPath dir ++ '\\' : pgm
 
-dosifyPath stuff
-  = subst '/' '\\' real_stuff
- where
-   -- fully convince myself that /cygdrive/ prefixes cannot
-   -- really appear here.
-  cygdrive_prefix = "/cygdrive/"
-
-  real_stuff
-    | cygdrive_prefix `isPrefixOf` stuff = dropList cygdrive_prefix stuff
-    | otherwise = stuff
-   
+subst a b ls = map (\ x -> if x == a then b else x) ls
 #else
-
---------------------- Unix version ---------------------
-dosifyPaths  ps  = ps
-unDosifyPath xs  = xs
-pgmPath dir pgm  = dir ++ '/' : pgm
-dosifyPath stuff = stuff
+--------------------- Non-Windows version --------------
+normalisePath xs   = xs
+pgmPath dir pgm    = dir ++ '/' : pgm
+platformPath stuff = stuff
 --------------------------------------------------------
 #endif
 
-subst a b ls = map (\ x -> if x == a then b else x) ls
 \end{code}
 
 
@@ -830,41 +885,36 @@ slash s1 s2 = s1 ++ ('/' : s2)
 
 \begin{code}
 -----------------------------------------------------------------------------
--- Define      getExecDir     :: IO (Maybe String)
+-- Define      getBaseDir     :: IO (Maybe String)
 
 #if defined(mingw32_HOST_OS)
-getExecDir :: IO (Maybe String)
-getExecDir = do let len = (2048::Int) -- plenty, PATH_MAX is 512 under Win32.
+getBaseDir :: IO (Maybe String)
+-- Assuming we are running ghc, accessed by path  $()/bin/ghc.exe,
+-- return the path $(stuff).  Note that we drop the "bin/" directory too.
+getBaseDir = do let len = (2048::Int) -- plenty, PATH_MAX is 512 under Win32.
                buf <- mallocArray len
                ret <- getModuleFileName nullPtr buf len
                if ret == 0 then free buf >> return Nothing
                            else do s <- peekCString buf
                                    free buf
-                                   return (Just (reverse (dropList "/bin/ghc.exe" (reverse (unDosifyPath s)))))
-
+                                   return (Just (rootDir s))
+  where
+    rootDir s = reverse (dropList "/bin/ghc.exe" (reverse (normalisePath s)))
 
 foreign import stdcall "GetModuleFileNameA" unsafe
   getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
 #else
-getExecDir :: IO (Maybe String) = do return Nothing
+getBaseDir :: IO (Maybe String) = do return Nothing
 #endif
 
 #ifdef mingw32_HOST_OS
 foreign import ccall "_getpid" unsafe getProcessID :: IO Int -- relies on Int == Int32 on Windows
 #elif __GLASGOW_HASKELL__ > 504
 getProcessID :: IO Int
-getProcessID = GHC.Posix.c_getpid >>= return . fromIntegral
+getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral
 #else
 getProcessID :: IO Int
 getProcessID = Posix.getProcessID
 #endif
 
-quote :: String -> String
-#if defined(mingw32_HOST_OS)
-quote "" = ""
-quote s  = "\"" ++ s ++ "\""
-#else
-quote s = s
-#endif
-
 \end{code}