[project @ 2000-07-18 14:50:07 by simonmar]
[ghc-hetmet.git] / ghc / driver / Main.hs
index 16544a6..7120b93 100644 (file)
@@ -5,6 +5,9 @@
 --
 -----------------------------------------------------------------------------
 
+-- with path so that ghc -M can find config.h
+#include "../includes/config.h"
+
 module Main (main) where
 
 import Package
@@ -12,18 +15,26 @@ import Config
 
 import RegexString
 import Concurrent
+#ifndef mingw32_TARGET_OS
 import Posix
+#endif
+import Directory
 import IOExts
 import Exception
 import Dynamic
 
 import IO
+import Monad
 import Array
 import List
 import System
 import Maybe
 import Char
 
+#ifdef mingw32_TARGET_OS
+foreign import "_getpid" getProcessID :: IO Int 
+#endif
+
 #define GLOBAL_VAR(name,value,ty)  \
 name = global (value) :: IORef (ty); \
 {-# NOINLINE name #-}
@@ -36,8 +47,9 @@ name = global (value) :: IORef (ty); \
 -- mkDLL
 -- java generation
 -- user ways
--- Win32 support
+-- Win32 support: proper signal handling
 -- make sure OPTIONS in .hs file propogate to .hc file if -C or -keep-hc-file-too
+-- reading the package configuration file is too slow
 
 -----------------------------------------------------------------------------
 -- Differences vs. old driver:
@@ -61,9 +73,9 @@ short_usage = do
   exitWith ExitSuccess
    
 long_usage = do
-  let usage_filename = "ghc-usage.txt"
-      usage_dir = findFile usage_filename cGHC_DRIVER_DIR
-  usage <- readFile (usage_dir ++ "/" ++ usage_filename)
+  let usage_file = "ghc-usage.txt"
+      usage_path = findFile usage_file (cGHC_DRIVER_DIR ++ '/':usage_file)
+  usage <- readFile usage_path
   dump usage
   exitWith ExitSuccess
   where
@@ -120,6 +132,7 @@ data BarfKind
   | PhaseFailed String ExitCode
   | Interrupted
   | NoInputFiles
+  | OtherError String
   deriving Eq
 
 GLOBAL_VAR(prog_name, "ghc", String)
@@ -146,6 +159,8 @@ showBarf (WayCombinationNotSupported ws)
        (map (showString . wayName . lkupWay) ws)
 showBarf (NoInputFiles)
    = showString "no input files"
+showBarf (OtherError str)
+   = showString str
 
 barfKindTc = mkTyCon "BarfKind"
 
@@ -156,16 +171,20 @@ instance Typeable BarfKind where
 -- Temporary files
 
 GLOBAL_VAR(files_to_clean, [], [String])
+GLOBAL_VAR(keep_tmp_files, False, Bool)
 
 cleanTempFiles :: IO ()
 cleanTempFiles = do
+  forget_it <- readIORef keep_tmp_files
+  unless forget_it $ do
+
   fs <- readIORef files_to_clean
   verb <- readIORef verbose
 
   let blowAway f =
           (do  on verb (hPutStrLn stderr ("removing: " ++ f))
                if '*' `elem` f then system ("rm -f " ++ f) >> return ()
-                               else removeLink f)
+                               else removeFile f)
            `catchAllIO`
           (\e -> on verb (hPutStrLn stderr 
                                ("warning: can't remove tmp file" ++ f)))
@@ -227,7 +246,11 @@ GLOBAL_VAR(dry_run,                False,          Bool)
 GLOBAL_VAR(recomp,             True,           Bool)
 GLOBAL_VAR(tmp_prefix,                 cTMPDIR,        String)
 GLOBAL_VAR(stolen_x86_regs,    4,              Int)
-GLOBAL_VAR(static,             True,           Bool)  -- ToDo: not for mingw32
+#if !defined(HAVE_WIN32_DLL_SUPPORT) || defined(DONT_WANT_WIN32_DLL_SUPPORT)
+GLOBAL_VAR(static,             True,           Bool)
+#else
+GLOBAL_VAR(static,              False,          Bool)
+#endif
 GLOBAL_VAR(collect_ghc_timing,         False,          Bool)
 GLOBAL_VAR(do_asm_mangling,    True,           Bool)
 
@@ -257,7 +280,8 @@ data HscLang
   | HscJava
 
 GLOBAL_VAR(hsc_lang, if cGhcWithNativeCodeGen == "YES" && 
-                        prefixMatch "i386" cTARGETPLATFORM
+                        (prefixMatch "i386" cTARGETPLATFORM ||
+                         prefixMatch "sparc" cTARGETPLATFORM)
                        then  HscAsm
                        else  HscC, 
           HscLang)
@@ -533,6 +557,84 @@ augment_library_paths path
 -----------------------------------------------------------------------------
 -- Packages
 
+GLOBAL_VAR(package_config, (findFile "package.conf" (cGHC_DRIVER_DIR++"/package.conf.inplace")), String)
+
+listPackages :: IO ()
+listPackages = do 
+  details <- readIORef package_details
+  hPutStr stdout (listPkgs details)
+  hPutChar stdout '\n'
+  exitWith ExitSuccess
+
+newPackage :: IO ()
+newPackage = do
+  checkConfigAccess
+  details <- readIORef package_details
+  hPutStr stdout "Reading package info from stdin... "
+  stuff <- getContents
+  let new_pkg = read stuff :: (String,Package)
+  catchAll new_pkg
+       (\e -> throwDyn (OtherError "parse error in package info"))
+  hPutStrLn stdout "done."
+  if (fst new_pkg `elem` map fst details)
+       then throwDyn (OtherError ("package `" ++ fst new_pkg ++ 
+                                       "' already installed"))
+       else do
+  conf_file <- readIORef package_config
+  savePackageConfig conf_file
+  maybeRestoreOldConfig conf_file $ do
+  writeNewConfig conf_file ( ++ [new_pkg])
+  exitWith ExitSuccess
+
+deletePackage :: String -> IO ()
+deletePackage pkg = do  
+  checkConfigAccess
+  details <- readIORef package_details
+  if (pkg `notElem` map fst details)
+       then throwDyn (OtherError ("package `" ++ pkg ++ "' not installed"))
+       else do
+  conf_file <- readIORef package_config
+  savePackageConfig conf_file
+  maybeRestoreOldConfig conf_file $ do
+  writeNewConfig conf_file (filter ((/= pkg) . fst))
+  exitWith ExitSuccess
+
+checkConfigAccess :: IO ()
+checkConfigAccess = do
+  conf_file <- readIORef package_config
+  access <- getPermissions conf_file
+  unless (writable access)
+       (throwDyn (OtherError "you don't have permission to modify the package configuration file"))
+
+maybeRestoreOldConfig :: String -> IO () -> IO ()
+maybeRestoreOldConfig conf_file io
+  = catchAllIO io (\e -> do
+        hPutStr stdout "\nWARNING: an error was encountered while the new \n\ 
+                      \configuration was being written.  Attempting to \n\ 
+                      \restore the old configuration... "
+        system ("cp " ++ conf_file ++ ".old " ++ conf_file)
+        hPutStrLn stdout "done."
+       throw e
+    )
+
+writeNewConfig :: String -> ([(String,Package)] -> [(String,Package)]) -> IO ()
+writeNewConfig conf_file fn = do
+  hPutStr stdout "Writing new package config file... "
+  old_details <- readIORef package_details
+  h <- openFile conf_file WriteMode
+  hPutStr h (dumpPackages (fn old_details))
+  hClose h
+  hPutStrLn stdout "done."
+
+savePackageConfig :: String -> IO ()
+savePackageConfig conf_file = do
+  hPutStr stdout "Saving old package config file... "
+    -- mv rather than cp because we've already done an hGetContents
+    -- on this file so we won't be able to open it for writing
+    -- unless we move the old one out of the way...
+  system ("mv " ++ conf_file ++ " " ++ conf_file ++ ".old")
+  hPutStrLn stdout "done."
+
 -- package list is maintained in dependency order
 packages = global ["std", "rts", "gmp"] :: IORef [String]
 -- comma in value, so can't use macro, grrr
@@ -545,11 +647,10 @@ addPackage package
          Nothing -> throwDyn (UnknownPackage package)
          Just details -> do
            ps <- readIORef packages
-           if package `elem` ps 
-               then return ()
-               else do mapM_ addPackage (package_deps details)
-                       ps <- readIORef packages
-                       writeIORef packages (package:ps)
+           unless (package `elem` ps) $ do
+               mapM_ addPackage (package_deps details)
+               ps <- readIORef packages
+               writeIORef packages (package:ps)
 
 getPackageImportPath   :: IO [String]
 getPackageImportPath = do
@@ -561,14 +662,14 @@ getPackageIncludePath   :: IO [String]
 getPackageIncludePath = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (nub (filter (not.null) (map include_dir ps')))
+  return (nub (filter (not.null) (concatMap include_dirs ps')))
 
        -- includes are in reverse dependency order (i.e. rts first)
 getPackageCIncludes   :: IO [String]
 getPackageCIncludes = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (reverse (nub (filter (not.null) (map c_include ps'))))
+  return (reverse (nub (filter (not.null) (concatMap c_includes ps'))))
 
 getPackageLibraryPath  :: IO [String]
 getPackageLibraryPath = do
@@ -588,26 +689,24 @@ getPackageExtraGhcOpts :: IO [String]
 getPackageExtraGhcOpts = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (map extra_ghc_opts ps')
+  return (concatMap extra_ghc_opts ps')
 
 getPackageExtraCcOpts  :: IO [String]
 getPackageExtraCcOpts = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (map extra_cc_opts ps')
+  return (concatMap extra_cc_opts ps')
 
 getPackageExtraLdOpts  :: IO [String]
 getPackageExtraLdOpts = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (map extra_ld_opts ps')
+  return (concatMap extra_ld_opts ps')
 
+getPackageDetails :: [String] -> IO [Package]
 getPackageDetails ps = do
   pkg_details <- readIORef package_details
-  let getDetails p =  case lookup p pkg_details of
-                       Just details -> return details
-                       Nothing -> error "getPackageDetails"
-  mapM getDetails ps
+  return [ pkg | p <- ps, Just pkg <- [ lookup p pkg_details ] ]
 
 GLOBAL_VAR(package_details, (error "package_details"), [(String,Package)])
 
@@ -1011,10 +1110,13 @@ main =
   do
        -- install signal handlers
    main_thread <- myThreadId
+
+#ifndef mingw32_TARGET_OS
    let sig_handler = Catch (raiseInThread main_thread 
                                (DynException (toDyn Interrupted)))
    installHandler sigQUIT sig_handler Nothing 
    installHandler sigINT  sig_handler Nothing
+#endif
 
    pgm    <- getProgName
    writeIORef prog_name pgm
@@ -1025,8 +1127,8 @@ main =
    argv'  <- setTopDir argv
 
    -- read the package configuration
-   let conf = findFile "package.conf" (cGHC_DRIVER_DIR++"/package.conf.inplace")
-   contents <- readFile conf
+   conf_file <- readIORef package_config
+   contents <- readFile conf_file
    writeIORef package_details (read contents)
 
    -- find the phase to stop after (i.e. -E, -C, -c, -S flags)
@@ -1039,6 +1141,11 @@ main =
    more_opts <- findBuildTag
    _ <- processArgs more_opts []
 
+   -- get the -v flag
+   verb <- readIORef verbose
+
+   when verb (hPutStrLn stderr ("Using package config file: " ++ conf_file))
+
    if stop_phase == MkDependHS         -- mkdependHS is special
        then do_mkdependHS flags2 srcs
        else do
@@ -1070,9 +1177,8 @@ main =
 
    o_files <- mapM compileFile phase_srcs
 
-   if do_linking
-       then do_link o_files unknown_srcs
-       else return ()
+   when do_linking $
+       do_link o_files unknown_srcs
 
 
 -- The following compilation pipeline algorithm is fairly hacky.  A
@@ -1123,7 +1229,8 @@ run_pipeline last_phase do_linking use_ofile orig_basename (phase, input_fn)
          case phase of
                Hsc -> case lang of
                            HscC   -> HCc
-                           HscAsm -> As
+                           HscAsm | split     -> SplitMangle
+                                  | otherwise -> As
 
                HCc  | mangle    -> Mangle
                     | otherwise -> As
@@ -1152,11 +1259,11 @@ run_pipeline last_phase do_linking use_ofile orig_basename (phase, input_fn)
                Ln -> True
                Mangle | keep_raw_s -> True -- first enhancement :)
                As | keep_s  -> True
-               Cc | keep_hc -> True
+               HCc | keep_hc -> True
                _other -> False
 
      output_fn <- 
-       (if phase == last_phase && not do_linking && use_ofile
+       (if next_phase > last_phase && not do_linking && use_ofile
            then do o_file <- readIORef output_file
                    case o_file of 
                        Just s  -> return s
@@ -1176,10 +1283,9 @@ run_pipeline last_phase do_linking use_ofile orig_basename (phase, input_fn)
 
        -- sadly, ghc -E is supposed to write the file to stdout.  We
        -- generate <file>.cpp, so we also have to cat the file here.
-     if (next_phase > last_phase && last_phase == Cpp)
-       then run_something "Dump pre-processed file to stdout"
-               ("cat " ++ output_fn)
-       else return ()
+     when (next_phase > last_phase && last_phase == Cpp) $
+       run_something "Dump pre-processed file to stdout"
+                     ("cat " ++ output_fn)
 
      run_pipeline last_phase do_linking use_ofile 
          orig_basename (next_phase, output_fn)
@@ -1193,7 +1299,7 @@ newTempName extn = do
   findTempName tmp_dir x
   where findTempName tmp_dir x = do
           let filename = tmp_dir ++ "/ghc" ++ show x ++ '.':extn
-          b  <- fileExist filename
+          b  <- doesFileExist filename
           if b then findTempName tmp_dir (x+1)
                else return filename
 
@@ -1202,11 +1308,9 @@ newTempName extn = do
 
 do_mkdependHS :: [String] -> [String] -> IO ()
 do_mkdependHS cmd_opts srcs = do
-
-    --         # They're not (currently) needed, but we need to quote any -#include options
-    -- foreach (@Cmd_opts) {
-    --            s/-#include.*$/'$&'/g;
-    -- };  
+   -- HACK
+   let quote_include_opt o | prefixMatch "-#include" o = "'" ++ o ++ "'"
+                           | otherwise                 = o
 
    mkdependHS      <- readIORef pgm_dep
    mkdependHS_opts <- getOpts opt_dep
@@ -1216,7 +1320,7 @@ do_mkdependHS cmd_opts srcs = do
        (unwords (mkdependHS : 
                      mkdependHS_opts
                   ++ hs_src_cpp_opts
-                  ++ ("--" : cmd_opts )
+                  ++ ("--" : map quote_include_opt cmd_opts )
                   ++ ("--" : srcs)
        ))
 
@@ -1336,7 +1440,7 @@ run_phase Hsc     basename input_fn output_fn
        let stub_c = basename ++ "_stub.c"
        
                -- copy .h_stub file into current dir if present
-       b <- fileExist tmp_stub_h
+       b <- doesFileExist tmp_stub_h
        on b (do
                run_something "Copy stub .h file"
                                ("cp " ++ tmp_stub_h ++ ' ':stub_h)
@@ -1370,9 +1474,8 @@ run_phase Hsc     basename input_fn output_fn
 run_phase cc_phase basename input_fn output_fn
    | cc_phase == Cc || cc_phase == HCc
    = do        cc <- readIORef pgm_c
-               cc_opts <- getOpts opt_c
+               cc_opts <- (getOpts opt_c)
                cmdline_include_dirs <- readIORef include_paths
-       -- ToDo: $c_flags .= " -mno-cygwin" if ( $TargetPlatform =~ /-mingw32$/ );
 
         let hcc = cc_phase == HCc
 
@@ -1425,6 +1528,9 @@ run_phase cc_phase basename input_fn output_fn
                   ++ [ verb, "-S", "-Wimplicit", opt_flag ]
                   ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
                   ++ cc_opts
+#ifdef mingw32_TARGET_OS
+                   ++ [" -mno-cygwin"]
+#endif
                   ++ include_paths
                   ++ pkg_extra_cc_opts
 --                ++ [">", ccout]
@@ -1574,19 +1680,17 @@ do_link o_files unknown_srcs = do
 run_something phase_name cmd
  = do
    verb <- readIORef verbose
-   if verb then do
+   when verb $ do
        putStr phase_name
        putStrLn ":"
        putStrLn cmd
-     else
-       return ()
 
    -- test for -n flag
    n <- readIORef dry_run
-   if n then return () else do 
+   unless n $ do 
 
    -- and run it!
-   exit_code <- system cmd  `catchAllIO` 
+   exit_code <- system ("sh -c \"" ++ cmd ++ "\"")  `catchAllIO` 
                   (\e -> throwDyn (PhaseFailed phase_name (ExitFailure 1)))
 
    if exit_code /= ExitSuccess
@@ -1676,10 +1780,10 @@ opts =
   ,  ( "keep-hc-file"   , AnySuffix (\_ -> writeIORef keep_hc_files True) )
   ,  ( "keep-s-file"    , AnySuffix (\_ -> writeIORef keep_s_files  True) )
   ,  ( "keep-raw-s-file", AnySuffix (\_ -> writeIORef keep_raw_s_files  True) )
+  ,  ( "keep-tmp-files" , AnySuffix (\_ -> writeIORef keep_tmp_files True) )
 
   ,  ( "split-objs"    , NoArg (if can_split
                                    then do writeIORef split_object_files True
-                                           writeIORef hsc_lang HscC
                                            add opt_C "-fglobalise-toplev-names"
                                            add opt_c "-DUSE_SPLIT_MARKERS"
                                    else hPutStrLn stderr
@@ -1701,6 +1805,10 @@ opts =
   ,  ( "package"        , HasArg (addPackage) )
   ,  ( "syslib"         , HasArg (addPackage) )        -- for compatibility w/ old vsns
 
+  ,  ( "-list-packages"  , NoArg (listPackages) )
+  ,  ( "-add-package"    , NoArg (newPackage) )
+  ,  ( "-delete-package" , SepArg (deletePackage) )
+
         ------- Specific phases  --------------------------------------------
   ,  ( "pgmdep"         , HasArg (writeIORef pgm_dep) )
   ,  ( "pgmL"           , HasArg (writeIORef pgm_L) )
@@ -1765,6 +1873,7 @@ opts =
 
   ,  ( "fasm"             , OptPrefix (\_ -> writeIORef hsc_lang HscAsm) )
 
+  ,  ( "fvia-c"                   , NoArg (writeIORef hsc_lang HscC) )
   ,  ( "fvia-C"                   , NoArg (writeIORef hsc_lang HscC) )
 
   ,  ( "fno-asm-mangling"  , NoArg (writeIORef do_asm_mangling False) )
@@ -1772,8 +1881,11 @@ opts =
   ,  ( "fmax-simplifier-iterations", 
                Prefix (writeIORef opt_MaxSimplifierIterations . read) )
 
-  ,  ( "fusagesp",             NoArg (do writeIORef opt_UsageSPInf True
-                                         add opt_C "-fusagesp-on") )
+  ,  ( "fusagesp"         , NoArg (do writeIORef opt_UsageSPInf True
+                                      add opt_C "-fusagesp-on") )
+
+  ,  ( "fstrictfp"        , NoArg (do add opt_C "-fstrictfp"
+                                      add opt_c "-ffloat-store"))
 
        -- flags that are "active negatives"
   ,  ( "fno-implicit-prelude"  , PassFlag (add opt_C) )
@@ -1866,9 +1978,8 @@ sizeOpt ref str
 writeSizeOpt :: IORef Integer -> Integer -> IO ()
 writeSizeOpt ref new = do
   current <- readIORef ref
-  if (new > current) 
-       then writeIORef ref new
-       else return ()
+  when (new > current) $
+       writeIORef ref new
 
 floatOpt :: IORef Double -> String -> IO ()
 floatOpt ref str
@@ -1893,7 +2004,7 @@ findFile name alt_path = unsafePerformIO (do
   top_dir <- readIORef topDir
   let installed_file = top_dir ++ '/':name
   let inplace_file   = top_dir ++ '/':cCURRENT_DIR ++ '/':alt_path
-  b <- fileExist inplace_file
+  b <- doesFileExist inplace_file
   if b  then return inplace_file
        else return installed_file
  )
@@ -1936,8 +2047,10 @@ global :: a -> IORef a
 global a = unsafePerformIO (newIORef a)
 
 split_filename :: String -> (String,String)
-split_filename f = (reverse rev_basename, reverse rev_ext)
-  where (rev_ext, '.':rev_basename) = span ('.' /=) (reverse f)
+split_filename f = (reverse (stripDot rev_basename), reverse rev_ext)
+  where (rev_ext, rev_basename) = span ('.' /=) (reverse f)
+        stripDot ('.':xs) = xs
+        stripDot xs       = xs
 
 split :: Char -> String -> [String]
 split c s = case rest of
@@ -1953,7 +2066,7 @@ add var x = do
 addNoDups :: Eq a => IORef [a] -> a -> IO ()
 addNoDups var x = do
   xs <- readIORef var
-  if x `elem` xs then return () else writeIORef var (x:xs)
+  unless (x `elem` xs) $ writeIORef var (x:xs)
 
 remove_suffix :: String -> Char -> String
 remove_suffix s c