[project @ 2001-07-05 13:31:09 by sewardj]
[ghc-hetmet.git] / ghc / compiler / main / SysTools.lhs
index 945ae44..33ac91c 100644 (file)
@@ -33,7 +33,7 @@ module SysTools (
 
        -- System interface
        getProcessID,           -- IO Int
-       System.system,          -- String -> IO Int     -- System.system
+       system,                 -- String -> IO Int
 
        -- Misc
        showGhcUsage,           -- IO ()        Shows usage message and exits
@@ -49,23 +49,32 @@ import Panic                ( progName, GhcException(..) )
 import Util            ( global )
 import CmdLineOpts     ( dynFlag, verbosity )
 
-import List            ( intersperse, isPrefixOf )
 import Exception       ( throwDyn, catchAllIO )
-import IO              ( openFile, hClose, IOMode(..),
-                         hPutStr, hPutChar, hPutStrLn, hFlush, stderr
-                       )
+import IO
 import Directory       ( doesFileExist, removeFile )
 import IOExts          ( IORef, readIORef, writeIORef )
 import Monad           ( when, unless )
-import qualified System
-import System          ( ExitCode(..) )
+import System          ( system, ExitCode(..), exitWith )
+import CString
+import Int
+
+#if __GLASGOW_HASKELL__ < 500
+import Storable
+#else
+import MarshalArray
+#endif
 
 #include "../includes/config.h"
 
 #if !defined(mingw32_TARGET_OS)
 import qualified Posix
+#else
+import Addr
+import List            ( isPrefixOf )
 #endif
 
+import List            ( isSuffixOf )
+
 #include "HsVersions.h"
 
 {-# DEPRECATED runSomething "runSomething should be private to SysTools" #-}
@@ -111,12 +120,39 @@ 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}
 %*                                                                     *
 %************************************************************************
 
+All these pathnames are maintained IN THE NATIVE FORMAT OF THE HOST MACHINE.
+(See remarks under pathnames below)
+
 \begin{code}
 GLOBAL_VAR(v_Pgm_L,    error "pgm_L",   String)        -- unlit
 GLOBAL_VAR(v_Pgm_P,    error "pgm_P",   String)        -- cpp
@@ -127,7 +163,6 @@ GLOBAL_VAR(v_Pgm_a,         error "pgm_a",   String)        -- as
 GLOBAL_VAR(v_Pgm_l,    error "pgm_l",   String)        -- ld
 GLOBAL_VAR(v_Pgm_MkDLL, error "pgm_dll", String)       -- mkdll
 
-GLOBAL_VAR(v_Pgm_PERL, error "pgm_PERL", String)       -- perl
 GLOBAL_VAR(v_Pgm_T,    error "pgm_T",    String)       -- touch
 GLOBAL_VAR(v_Pgm_CP,   error "pgm_CP",          String)        -- cp
 
@@ -160,36 +195,41 @@ initSysTools minusB_args
                -- top_dir
                --      for "installed" this is the root of GHC's support files
                --      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   pgm = top_dir `slash` "extra-bin" `slash` pgm
-             inplace dir pgm = top_dir `slash` dir         `slash` pgm
-
-       ; let pkgconfig_path | am_installed = top_dir `slash` "package.conf"
-                            | otherwise    = top_dir `slash` cGHC_DRIVER_DIR `slash` "package.conf.inplace"
-
-       -- Check that the in-place package config exists if 
-       -- the installed one does not (we need at least one!)
-       ; config_exists <- doesFileExist pkgconfig_path
-       ; if config_exists then return ()
-         else throwDyn (InstallationError 
-                          ("Can't find package.conf in " ++ pkgconfig_path))
+       ; 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
 
-       -- The GHC usage help message is found similarly to the package configuration
-       ; let ghc_usage_msg_path | am_installed = installed "ghc-usage.txt"
-                                | otherwise    = inplace cGHC_DRIVER_DIR "ghc-usage.txt"
+       ; let pkgconfig_path
+               | am_installed = installed "package.conf"
+               | otherwise    = inplace cGHC_DRIVER_DIR "package.conf.inplace"
 
+             ghc_usage_msg_path
+               | am_installed = installed "ghc-usage.txt"
+               | otherwise    = inplace cGHC_DRIVER_DIR "ghc-usage.txt"
 
-       -- For all systems, unlit, split, mangle are GHC utilities
-       -- architecture-specific stuff is done when building Config.hs
-       ; let unlit_path  | am_installed = installed cGHC_UNLIT
-                         | otherwise    = inplace cGHC_UNLIT_DIR cGHC_UNLIT
+               -- For all systems, unlit, split, mangle are GHC utilities
+               -- architecture-specific stuff is done when building Config.hs
+             unlit_path
+               | am_installed = installed_bin cGHC_UNLIT
+               | otherwise    = inplace cGHC_UNLIT_DIR cGHC_UNLIT
 
                -- split and mangle are Perl scripts
-             split_script  | am_installed = installed cGHC_SPLIT
-                           | otherwise    = inplace cGHC_SPLIT_DIR cGHC_SPLIT
-             mangle_script | am_installed = installed cGHC_MANGLER
-                           | otherwise    = inplace cGHC_MANGLER_DIR cGHC_MANGLER
+             split_script
+               | am_installed = installed_bin cGHC_SPLIT
+               | otherwise    = inplace cGHC_SPLIT_DIR cGHC_SPLIT
+
+             mangle_script
+               | am_installed = installed_bin cGHC_MANGLER
+               | otherwise    = inplace cGHC_MANGLER_DIR cGHC_MANGLER
 
+       -- Check that the package config exists
+       ; config_exists <- doesFileExist pkgconfig_path
+       ; when (not config_exists) $
+            throwDyn (InstallationError 
+                        ("Can't find package.conf as " ++ pkgconfig_path))
 
 #if defined(mingw32_TARGET_OS)
        --              WINDOWS-SPECIFIC STUFF
@@ -197,15 +237,23 @@ 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 "lib/gcc-lib/" 
+                                         ++ " -I" ++ installed "include/w32api:" 
+                                                  ++ installed "include/mingw")
                        | otherwise    = cGCC
-             perl_path | am_installed = installed cGHC_PERL
+             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 
@@ -219,23 +267,22 @@ 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
-               perl_path  = cGHC_PERL
-               mkdll_path = panic "Cant build DLLs on a non-Win32 system"
+               mkdll_path = panic "Can't build DLLs on a non-Win32 system"
 
-       -- On Unix, for some historical reason, we do an install-time
-       -- configure to find Perl, and slam that on the front of
-       -- the installed script; so we can invoke them directly 
-       -- (not via perl)
-       -- a call to Perl to get the invocation of split and mangle
+       -- On Unix, scripts are invoked using the '#!' method.  Binary
+       -- installations of GHC on Unix place the correct line on the front
+       -- of the script at installation time, so we don't want to wire-in
+       -- our knowledge of $(PERL) on the host system here.
        ; let split_path  = split_script
              mangle_path = mangle_script
-
 #endif
 
-       -- For all systems, copy and remove are provided by the host 
+       -- 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
        
@@ -262,7 +309,6 @@ initSysTools minusB_args
        ; writeIORef v_Pgm_MkDLL           mkdll_path
        ; writeIORef v_Pgm_T               touch_path
        ; writeIORef v_Pgm_CP              cp_path
-       ; writeIORef v_Pgm_PERL            perl_path
 
        ; return top_dir
        }
@@ -296,7 +342,7 @@ setPgm pgm     = unknownFlagErr ("-pgm" ++ pgm)
 -- 1. Set proto_top_dir
 --     a) look for (the last) -B flag, and use it
 --     b) if there are no -B flags, get the directory 
---        where GHC is running
+--        where GHC is running (only on Windows)
 --
 -- 2. If package.conf exists in proto_top_dir, we are running
 --     installed; and TopDir = proto_top_dir
@@ -309,41 +355,42 @@ setPgm pgm           = unknownFlagErr ("-pgm" ++ pgm)
 
 getTopDir :: [String]
          -> IO (Bool,          -- True <=> am installed, False <=> in-place
-                String)        -- TopDir
+                String)        -- TopDir (in Unix format '/' separated)
 
 getTopDir minusbs
-  = do { proto_top_dir <- get_proto
-
-       -- Discover whether we're running in a build tree or in an installation,
+  = do { top_dir <- get_proto
+        -- Discover whether we're running in a build tree or in an installation,
        -- by looking for the package configuration file.
-       ; am_installed <- doesFileExist (proto_top_dir `slash` "package.conf")
+       ; am_installed <- doesFileExist (top_dir `slash` "package.conf")
 
-       ; if am_installed then
-           return (True, proto_top_dir)
-        else
-           return (False, remove_suffix proto_top_dir)
+       ; return (am_installed, top_dir)
        }
   where
-    get_proto | not (null minusbs) 
-             = return (dosifyPath (drop 2 (last minusbs)))
+    -- get_proto returns a Unix-format path
+    get_proto | not (null minusbs)
+             = return (unDosifyPath (drop 2 (last minusbs)))   -- 2 for "-B"
              | otherwise          
-             = do { maybe_exec_dir <- getExecDir       -- Get directory of executable
-                  ; case maybe_exec_dir of             -- (only works on Windows)
-                       Nothing  -> throwDyn (InstallationError ("missing -B<dir> option"))
-                       Just dir -> return dir }
-
-    remove_suffix dir  -- "/...stuff.../ghc/compiler" --> "/...stuff..."
-       = ASSERT2( not (null p1) && 
-                  not (null p2) && 
-                  dosifyPath dir == dosifyPath (top_dir ++ "/ghc/compiler"),
-                  text dir )
-         top_dir
+             = do { maybe_exec_dir <- getExecDir -- Get directory of executable
+                  ; 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))
+                  }
+
+    -- 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 dir)
+        p1      = dropWhile (not . isSlash) (reverse ghc_bin_dir)
         p2      = dropWhile (not . isSlash) (tail p1)  -- head is '/'
-        top_dir = reverse (tail p2)                    -- head is '/'
-
-getExecDir = return Nothing
+        back_two = reverse (tail p2)                   -- head is '/'
+        back_one = reverse (tail p1)
 \end{code}
 
 
@@ -392,8 +439,15 @@ touch purpose arg =  do p <- readIORef v_Pgm_T
                        runSomething purpose p [arg]
 
 copy :: String -> String -> String -> IO ()
-copy purpose from to = do p <- readIORef v_Pgm_CP
-                         runSomething purpose p [from,to]
+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}
@@ -414,7 +468,7 @@ Show the usage message and exit
 showGhcUsage = do { usage_path <- readIORef v_Path_usage
                  ; usage      <- readFile usage_path
                  ; dump usage
-                 ; System.exitWith System.ExitSuccess }
+                 ; exitWith ExitSuccess }
   where
      dump ""         = return ()
      dump ('$':'$':s) = hPutStr stderr progName >> dump s
@@ -430,9 +484,6 @@ packageConfigPath = readIORef v_Path_package_config
 %*                                                                     *
 %************************************************************************
 
-One reason this code is here is because SysTools.system needs to make
-a temporary file.
-
 \begin{code}
 GLOBAL_VAR(v_FilesToClean, [],               [String] )
 GLOBAL_VAR(v_TmpDir,       cDEFAULT_TMPDIR,  String   )
@@ -475,12 +526,14 @@ addFilesToClean files = mapM_ (add v_FilesToClean) files
 removeTmpFiles :: Int -> [FilePath] -> IO ()
 removeTmpFiles verb fs
   = traceCmd "Deleting temp files" 
-            ("Deleting: " ++ concat (intersperse " " 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}
 
@@ -504,18 +557,19 @@ runSomething :: String            -- For -v message
             -> String          -- Command name (possibly a full path)
                                --      assumed already dos-ified
             -> [String]        -- Arguments
-                               --      runSomthing will dos-ify them
+                               --      runSomething will dos-ify them
             -> IO ()
 
 runSomething phase_name pgm args
  = traceCmd phase_name cmd_line $
-   do   { exit_code <- System.system cmd_line
+   do   { exit_code <- system cmd_line
        ; if exit_code /= ExitSuccess
          then throwDyn (PhaseFailed phase_name exit_code)
          else return ()
        }
   where
     cmd_line = unwords (pgm : dosifyPaths args)
+       -- The pgm is already in native format (appropriate dir separators)
 
 traceCmd :: String -> String -> IO () -> IO ()
 -- a) trace the command (at two levels of verbosity)
@@ -542,24 +596,47 @@ traceCmd phase_name cmd_line action
 
 %************************************************************************
 %*                                                                     *
-\subsection{Support code}
+\subsection{Path names}
 %*                                                                     *
 %************************************************************************
 
+We maintain path names in Unix form ('/'-separated) right until 
+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,
+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]
-dosifyPath  :: String -> String
--- dosifyPath does two things
+-- dosifyPaths does two things
 -- a) change '/' to '\'
 -- b) remove initial '/cygdrive/'
 
+unDosifyPath :: String -> String
+-- Just change '\' to '/'
+
+pgmPath :: String              -- Directory string in Unix format
+       -> String               -- Program name with no directory separators
+                               --      (e.g. copy /y)
+       -> String               -- Program invocation string in native format
+
+
+
 #if defined(mingw32_TARGET_OS)
+
+--------------------- Windows version ------------------
+unDosifyPath xs = xs
+
 dosifyPaths xs = map dosifyPath xs
 
+pgmPath dir pgm = dosifyPath dir ++ '\\' : pgm
+
 dosifyPath stuff
   = subst '/' '\\' real_stuff
  where
@@ -571,22 +648,27 @@ dosifyPath stuff
     | cygdrive_prefix `isPrefixOf` stuff = drop (length cygdrive_prefix) stuff
     | otherwise = stuff
    
-  subst a b ls = map (\ x -> if x == a then b else x) ls
 #else
-dosifyPaths xs = xs
-dosifyPath  xs = xs
+
+--------------------- Unix version ---------------------
+dosifyPaths  ps = ps
+unDosifyPath xs = subst '\\' '/' xs
+pgmPath dir pgm = dir ++ '/' : pgm
+--------------------------------------------------------
 #endif
 
+subst a b ls = map (\ x -> if x == a then b else x) ls
+\end{code}
+
+
 -----------------------------------------------------------------------------
--- Path name construction
---     At the moment, we always use '/' and rely on dosifyPath 
---     to switch to DOS pathnames when necessary
+   Path name construction
 
+\begin{code}
 slash           :: String -> String -> String
 absPath, relPath :: [String] -> String
 
 isSlash '/'   = True
-isSlash '\\'  = True
 isSlash other = False
 
 relPath [] = ""
@@ -594,21 +676,49 @@ relPath xs = foldr1 slash xs
 
 absPath xs = "" `slash` relPath xs
 
-#if defined(mingw32_TARGET_OS)
-slash s1 s2 = s1 ++ ('\\' : s2)
-#else
 slash s1 s2 = s1 ++ ('/' : s2)
-#endif
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
+\subsection{Support code}
+%*                                                                     *
+%************************************************************************
 
+\begin{code}
 -----------------------------------------------------------------------------
--- Convert filepath into MSDOS form.
--- 
 -- Define      myGetProcessId :: IO Int
+--             getExecDir     :: IO (Maybe String)
 
 #ifdef mingw32_TARGET_OS
-foreign import "_getpid" getProcessID :: IO Int 
+foreign import "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
+
+#if __GLASGOW_HASKELL__ >= 500
+foreign import stdcall "GetCurrentDirectoryA" getCurrentDirectory :: Int32 -> CString -> IO Int32
+foreign import stdcall "GetCurrentDirectoryA" getCurrentDirectoryLen :: Int32 -> Addr -> IO Int32
+getExecDir :: IO (Maybe String)
+getExecDir = do len <- getCurrentDirectoryLen 0 nullAddr
+               buf <- mallocArray (fromIntegral len)
+               ret <- getCurrentDirectory len buf
+               if ret == 0 then return Nothing
+                           else do s <- peekCString buf
+                                   destructArray (fromIntegral len) buf
+                                   return (Just s)
+#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)
+#endif
 #else
 getProcessID :: IO Int
 getProcessID = Posix.getProcessID
+getExecDir :: IO (Maybe String) = do return Nothing
 #endif
 \end{code}