[project @ 2001-08-10 23:08:25 by sof]
[ghc-hetmet.git] / ghc / compiler / main / SysTools.lhs
index 7e6a0f1..adc8e0c 100644 (file)
@@ -17,13 +17,14 @@ module SysTools (
                                -- Where package.conf is
 
        -- Interface to system tools
-       runUnlit, runCpp, runCc, -- [String] -> IO ()
-       runMangle, runSplit,     -- [String] -> IO ()
-       runAs, runLink,          -- [String] -> IO ()
+       runUnlit, runCpp, runCc, -- [Option] -> IO ()
+       runMangle, runSplit,     -- [Option] -> IO ()
+       runAs, runLink,          -- [Option] -> IO ()
        runMkDLL,
 
        touch,                  -- String -> String -> IO ()
        copy,                   -- String -> String -> String -> IO ()
+       unDosifyPath,           -- String -> String
        
        -- Temporary-file management
        setTmpDir,
@@ -33,13 +34,14 @@ module SysTools (
 
        -- System interface
        getProcessID,           -- IO Int
-       system,                 -- String -> IO Int
+       system,                 -- String -> IO ExitCode
 
        -- Misc
        showGhcUsage,           -- IO ()        Shows usage message and exits
        getSysMan,              -- IO String    Parallel system only
+       
+       Option(..)
 
-       runSomething    -- ToDo: make private
  ) where
 
 import DriverUtil
@@ -54,31 +56,23 @@ import IO
 import Directory       ( doesFileExist, removeFile )
 import IOExts          ( IORef, readIORef, writeIORef )
 import Monad           ( when, unless )
-import System          ( system, ExitCode(..), exitWith )
+import System          ( ExitCode(..), exitWith, getEnv, system )
 import CString
 import Int
-
-#if __GLASGOW_HASKELL__ < 500
-import Storable
-#else
-import MarshalArray
-#endif
-
+import Addr
+    
 #include "../includes/config.h"
 
-#if !defined(mingw32_TARGET_OS)
+#ifndef mingw32_TARGET_OS
 import qualified Posix
 #else
-import Addr
 import List            ( isPrefixOf )
+import MarshalArray
+import SystemExts       ( rawSystem )
 #endif
 
-import List            ( isSuffixOf )
-
 #include "HsVersions.h"
 
-{-# DEPRECATED runSomething "runSomething should be private to SysTools" #-}
-
 \end{code}
 
 
@@ -120,6 +114,30 @@ Config.hs contains two sorts of things
                
 
 
+---------------------------------------------
+NOTES for an ALTERNATIVE scheme (i.e *not* what is currently implemented):
+
+Another hair-brained scheme for simplifying the current tool location
+nightmare in GHC: Simon originally suggested using another
+configuration file along the lines of GCC's specs file - which is fine
+except that it means adding code to read yet another configuration
+file.  What I didn't notice is that the current package.conf is
+general enough to do this:
+
+Package
+    {name = "tools",    import_dirs = [],  source_dirs = [],
+     library_dirs = [], hs_libraries = [], extra_libraries = [],
+     include_dirs = [], c_includes = [],   package_deps = [],
+     extra_ghc_opts = ["-pgmc/usr/bin/gcc","-pgml${libdir}/bin/unlit", ... etc.],
+     extra_cc_opts = [], extra_ld_opts = []}
+
+Which would have the advantage that we get to collect together in one
+place the path-specific package stuff with the path-specific tool
+stuff.
+               End of NOTES
+---------------------------------------------
+
+
 %************************************************************************
 %*                                                                     *
 \subsection{Global variables to contain system programs}
@@ -173,7 +191,8 @@ initSysTools minusB_args
                --      for "in-place" it is the root of the build tree
                -- NB: top_dir is assumed to be in standard Unix format '/' separated
 
-       ; let installed_bin pgm   =  pgmPath (top_dir `slash` "bin") pgm
+       ; let installed, installed_bin :: FilePath -> FilePath
+              installed_bin pgm   =  pgmPath (top_dir `slash` "extra-bin") pgm
              installed     file  =  pgmPath top_dir file
              inplace dir   pgm   =  pgmPath (top_dir `slash` dir) pgm
 
@@ -200,6 +219,14 @@ initSysTools minusB_args
                | am_installed = installed_bin cGHC_MANGLER
                | otherwise    = inplace cGHC_MANGLER_DIR cGHC_MANGLER
 
+#ifndef mingw32_TARGET_OS
+       -- check whether TMPDIR is set in the environment
+       ; IO.try (do dir <- getEnv "TMPDIR" -- fails if not set
+                    setTmpDir dir
+                    return ()
+                 )
+#endif
+
        -- Check that the package config exists
        ; config_exists <- doesFileExist pkgconfig_path
        ; when (not config_exists) $
@@ -212,21 +239,36 @@ initSysTools minusB_args
        --      so when "installed" we look in TopDir/bin
        -- When "in-place" we look wherever the build-time configure 
        --      script found them
-       ; let cpp_path  | am_installed = installed cRAWCPP
-                       | otherwise    = cRAWCPP
-             gcc_path  | am_installed = installed cGCC
+       -- When "install" we tell gcc where its specs file + exes are (-B)
+       --      and also some places to pick up include files.  We need
+       --      to be careful to put all necessary exes in the -B place
+       --      (as, ld, cc1, etc) since if they don't get found there, gcc
+       --      then tries to run unadorned "as", "ld", etc, and will
+       --      pick up whatever happens to be lying around in the path,
+       --      possibly including those from a cygwin install on the target,
+       --      which is exactly what we're trying to avoid.
+       ; let gcc_path  | am_installed = installed_bin ("gcc -B\"" ++ installed "gcc-lib/\"")
                        | otherwise    = cGCC
-             perl_path | am_installed = installed cGHC_PERL
+               -- The trailing "/" is absolutely essential; gcc seems
+               -- to construct file names simply by concatenating to this
+               -- -B path with no extra slash
+               -- We use "/" rather than "\\" because otherwise "\\\" is mangled
+               -- later on; although gcc_path is in NATIVE format, gcc can cope
+               --      (see comments with declarations of global variables)
+               --
+               -- The quotes round the -B argument are in case TopDir has spaces in it
+
+             perl_path | am_installed = installed_bin cGHC_PERL
                        | otherwise    = cGHC_PERL
 
        -- 'touch' is a GHC util for Windows, and similarly unlit, mangle
-       ; let touch_path  | am_installed = installed cGHC_TOUCHY
+       ; let touch_path  | am_installed = installed_bin cGHC_TOUCHY
                          | otherwise    = inplace cGHC_TOUCHY_DIR cGHC_TOUCHY
 
        -- On Win32 we don't want to rely on #!/bin/perl, so we prepend 
        -- a call to Perl to get the invocation of split and mangle
-       ; let split_path  = perl_path ++ " " ++ split_script
-             mangle_path = perl_path ++ " " ++ mangle_script
+       ; let split_path  = perl_path ++ " \"" ++ split_script ++ "\""
+             mangle_path = perl_path ++ " \"" ++ mangle_script ++ "\""
 
        ; let mkdll_path = cMKDLL
 #else
@@ -234,8 +276,7 @@ initSysTools minusB_args
        -- On Unix, the "standard" tools are assumed to be
        -- in the same place whether we are running "in-place" or "installed"
        -- That place is wherever the build-time configure script found them.
-       ; let   cpp_path   = cRAWCPP
-               gcc_path   = cGCC
+       ; let   gcc_path   = cGCC
                touch_path = cGHC_TOUCHY
                mkdll_path = panic "Can't build DLLs on a non-Win32 system"
 
@@ -245,9 +286,11 @@ initSysTools minusB_args
        -- our knowledge of $(PERL) on the host system here.
        ; let split_path  = split_script
              mangle_path = mangle_script
-
 #endif
 
+       -- cpp is derived from gcc on all platforms
+        ; let cpp_path  = gcc_path ++ " -E " ++ cRAWCPP_FLAGS
+
        -- For all systems, copy and remove are provided by the host
        -- system; architecture-specific stuff is done when building Config.hs
        ; let   cp_path = cGHC_CP
@@ -325,9 +368,6 @@ getTopDir :: [String]
 
 getTopDir minusbs
   = do { top_dir <- get_proto
-       ; print top_dir
-       ; if "/ghc/compiler" `isSuffixOf` top_dir then print (remove_suffix top_dir) else print "not"
-
         -- Discover whether we're running in a build tree or in an installation,
        -- by looking for the package configuration file.
        ; am_installed <- doesFileExist (top_dir `slash` "package.conf")
@@ -335,7 +375,7 @@ getTopDir minusbs
        ; return (am_installed, top_dir)
        }
   where
-    -- get_proto returns a Unix-format path
+    -- get_proto returns a Unix-format path (relying on getExecDir to do so too)
     get_proto | not (null minusbs)
              = return (unDosifyPath (drop 2 (last minusbs)))   -- 2 for "-B"
              | otherwise          
@@ -343,23 +383,43 @@ getTopDir minusbs
                   ; case maybe_exec_dir of       -- (only works on Windows; 
                                                  --  returns Nothing on Unix)
                        Nothing  -> throwDyn (InstallationError "missing -B<dir> option")
-                       Just dir -> return (remove_suffix (unDosifyPath dir))
+                       Just dir -> return dir
                   }
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
+\subsection{Command-line options}
+n%*                                                                    *
+%************************************************************************
+
+When invoking external tools as part of the compilation pipeline, we
+pass these a sequence of options on the command-line. Rather than
+just using a list of Strings, we use a type that allows us to distinguish
+between filepaths and 'other stuff'. [The reason being, of course, that
+this type gives us a handle on transforming filenames, and filenames only,
+to whatever format they're expected to be on a particular platform.]
+
+
+\begin{code}
+data Option
+ = FileOption String
+ | Option     String
+showOptions :: [Option] -> String
+showOptions ls = unwords (map (quote.showOpt) ls)
+ where
+   showOpt (FileOption f) = dosifyPath f
+   showOpt (Option s)     = s
+
+#if defined(mingw32_TARGET_OS)
+   quote "" = ""
+   quote s  = "\"" ++ s ++ "\""
+#else
+   quote = id
+#endif
 
-    -- In an installed tree, the ghc binary lives in $libexecdir, which
-    -- is normally $libdir/bin.  So we strip off a /bin suffix here.
-    -- In a build tree, the ghc binary lives in $fptools/ghc/compiler,
-    -- so we strip off the /ghc/compiler suffix here too, leaving a
-    -- standard TOPDIR.
-    remove_suffix ghc_bin_dir  -- ghc_bin_dir is in standard Unix format
-       | "/ghc/compiler" `isSuffixOf` ghc_bin_dir      = back_two
-       | "/bin" `isSuffixOf` ghc_bin_dir               = back_one
-       | otherwise                                     = ghc_bin_dir
-       where
-        p1      = dropWhile (not . isSlash) (reverse ghc_bin_dir)
-        p2      = dropWhile (not . isSlash) (tail p1)  -- head is '/'
-        back_two = reverse (tail p2)                   -- head is '/'
-        back_one = reverse (tail p1)
 \end{code}
 
 
@@ -371,51 +431,52 @@ n%*                                                                       *
 
 
 \begin{code}
-runUnlit :: [String] -> IO ()
+runUnlit :: [Option] -> IO ()
 runUnlit args = do p <- readIORef v_Pgm_L
                   runSomething "Literate pre-processor" p args
 
-runCpp :: [String] -> IO ()
+runCpp :: [Option] -> IO ()
 runCpp args =   do p <- readIORef v_Pgm_P
                   runSomething "C pre-processor" p args
 
-runCc :: [String] -> IO ()
+runCc :: [Option] -> IO ()
 runCc args =   do p <- readIORef v_Pgm_c
                  runSomething "C Compiler" p args
 
-runMangle :: [String] -> IO ()
+runMangle :: [Option] -> IO ()
 runMangle args = do p <- readIORef v_Pgm_m
                    runSomething "Mangler" p args
 
-runSplit :: [String] -> IO ()
+runSplit :: [Option] -> IO ()
 runSplit args = do p <- readIORef v_Pgm_s
                   runSomething "Splitter" p args
 
-runAs :: [String] -> IO ()
+runAs :: [Option] -> IO ()
 runAs args = do p <- readIORef v_Pgm_a
                runSomething "Assembler" p args
 
-runLink :: [String] -> IO ()
+runLink :: [Option] -> IO ()
 runLink args = do p <- readIORef v_Pgm_l
                  runSomething "Linker" p args
 
-runMkDLL :: [String] -> IO ()
+runMkDLL :: [Option] -> IO ()
 runMkDLL args = do p <- readIORef v_Pgm_MkDLL
                   runSomething "Make DLL" p args
 
 touch :: String -> String -> IO ()
 touch purpose arg =  do p <- readIORef v_Pgm_T
-                       runSomething purpose p [arg]
+                       runSomething purpose p [FileOption arg]
 
 copy :: String -> String -> String -> IO ()
-copy purpose from to =
-    (do
-      h <- openFile to WriteMode
-      ls <- readFile from -- inefficient, but it'll do for now.
-                             -- ToDo: speed up via slurping.
-      hPutStrLn h ls
-      hClose h) `catchAllIO`
-                (\_ -> throwDyn (PhaseFailed purpose (ExitFailure 1)))
+copy purpose from to = do
+  verb <- dynFlag verbosity
+  when (verb >= 2) $ hPutStrLn stderr ("*** " ++ purpose)
+
+  h <- openFile to WriteMode
+  ls <- readFile from -- inefficient, but it'll do for now.
+                     -- ToDo: speed up via slurping.
+  hPutStr h ls
+  hClose h
 \end{code}
 
 \begin{code}
@@ -497,9 +558,11 @@ removeTmpFiles verb fs
             ("Deleting: " ++ unwords fs)
             (mapM_ rm fs)
   where
-    rm f = removeFile f `catchAllIO`
-               (\exn -> hPutStrLn stderr ("Warning: deleting non-existent " ++ f) >>
-                        return ())
+    rm f = removeFile f `catchAllIO` 
+               (\_ignored -> 
+                   when (verb >= 2) $
+                     hPutStrLn stderr ("Warning: deleting non-existent " ++ f)
+               )
 
 \end{code}
 
@@ -522,20 +585,31 @@ setDryRun = writeIORef v_Dry_run True
 runSomething :: String         -- For -v message
             -> String          -- Command name (possibly a full path)
                                --      assumed already dos-ified
-            -> [String]        -- Arguments
+            -> [Option]        -- Arguments
                                --      runSomething will dos-ify them
             -> IO ()
 
 runSomething phase_name pgm args
  = traceCmd phase_name cmd_line $
-   do   { exit_code <- system cmd_line
+   do   {
+#ifndef mingw32_TARGET_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
-    cmd_line = unwords (pgm : dosifyPaths args)
+    cmd_line = pgm ++ ' ':showOptions args -- unwords (pgm : dosifyPaths (map quote args))
        -- The pgm is already in native format (appropriate dir separators)
+#if defined(mingw32_TARGET_OS)
+    quote "" = ""
+    quote s  = "\"" ++ s ++ "\""
+#else
+    quote = id
+#endif
 
 traceCmd :: String -> String -> IO () -> IO ()
 -- a) trace the command (at two levels of verbosity)
@@ -597,10 +671,10 @@ pgmPath :: String         -- Directory string in Unix format
 #if defined(mingw32_TARGET_OS)
 
 --------------------- Windows version ------------------
-unDosifyPath xs = xs
-
 dosifyPaths xs = map dosifyPath xs
 
+unDosifyPath xs = subst '\\' '/' xs
+
 pgmPath dir pgm = dosifyPath dir ++ '\\' : pgm
 
 dosifyPath stuff
@@ -617,9 +691,10 @@ dosifyPath stuff
 #else
 
 --------------------- Unix version ---------------------
-dosifyPaths  ps = ps
-unDosifyPath xs = subst '\\' '/' xs
-pgmPath dir pgm = dir ++ '/' : pgm
+dosifyPaths  ps  = ps
+unDosifyPath xs  = xs
+pgmPath dir pgm  = dir ++ '/' : pgm
+dosifyPath stuff = stuff
 --------------------------------------------------------
 #endif
 
@@ -654,37 +729,28 @@ slash s1 s2 = s1 ++ ('/' : s2)
 
 \begin{code}
 -----------------------------------------------------------------------------
--- Define      myGetProcessId :: IO Int
---             getExecDir     :: IO (Maybe String)
-
-#ifdef mingw32_TARGET_OS
-foreign import "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
+-- Define      getExecDir     :: IO (Maybe String)
 
-#if __GLASGOW_HASKELL__ >= 500
-foreign import stdcall "GetCurrentDirectoryA" getCurrentDirectory :: Int32 -> CString -> IO Int32
-foreign import stdcall "GetCurrentDirectoryA" getCurrentDirectoryLen :: Int32 -> Addr -> IO Int32
+#if defined(mingw32_TARGET_OS)
 getExecDir :: IO (Maybe String)
-getExecDir = do len <- getCurrentDirectoryLen 0 nullAddr
+getExecDir = do let len = 2048 -- plenty, PATH_MAX is 512 under Win32.
                buf <- mallocArray (fromIntegral len)
-               ret <- getCurrentDirectory len buf
+               ret <- getModuleFileName nullAddr buf len
                if ret == 0 then return Nothing
                            else do s <- peekCString buf
                                    destructArray (fromIntegral len) buf
-                                   return (Just s)
+                                   return (Just (reverse (drop (length "/bin/ghc.exe") (reverse (unDosifyPath s)))))
+
+
+foreign import stdcall "GetModuleFileNameA" getModuleFileName :: Addr -> CString -> Int32 -> IO Int32
 #else
-foreign import stdcall "GetCurrentDirectoryA" getCurrentDirectory :: Int32 -> Addr -> IO Int32
-getExecDir :: IO (Maybe String)
-getExecDir = do len <- getCurrentDirectory 0 nullAddr
-               buf <- malloc (fromIntegral len)
-               ret <- getCurrentDirectory len buf
-               if ret == 0 then return Nothing
-                           else do s <- unpackCStringIO buf
-                                   free buf
-                                   return (Just s)
+getExecDir :: IO (Maybe String) = do return Nothing
 #endif
+
+#ifdef mingw32_TARGET_OS
+foreign import "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
 #else
 getProcessID :: IO Int
 getProcessID = Posix.getProcessID
-getExecDir :: IO (Maybe String) = do return Nothing
 #endif
 \end{code}