[project @ 2003-08-17 01:36:54 by sof]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
index 80a6c27..2b51934 100644 (file)
@@ -1,5 +1,7 @@
+{-# OPTIONS -fglasgow-exts #-}
+
 -----------------------------------------------------------------------------
--- $Id: Main.hs,v 1.25 2002/06/12 22:04:27 wolfgang Exp $
+-- $Id: Main.hs,v 1.35 2003/08/17 01:36:54 sof Exp $
 --
 -- Package management tool
 -----------------------------------------------------------------------------
@@ -8,11 +10,16 @@ module Main where
 
 import Package
 
-#ifdef __GLASGOW_HASKELL__
-import qualified Exception
-#endif
+#if __GLASGOW_HASKELL__ >= 504
+import System.Console.GetOpt
+import Text.PrettyPrint
+import qualified Control.Exception as Exception
+#else
 import GetOpt
 import Pretty
+import qualified Exception
+#endif
+
 import Monad
 import Directory
 import System  ( getEnv, getArgs, 
@@ -27,7 +34,13 @@ import ParsePkgConfLite
 #include "../../includes/config.h"
 
 #ifdef mingw32_HOST_OS
-import Win32DLL
+import Foreign
+
+#if __GLASGOW_HASKELL__ >= 504
+import Foreign.C.String
+#else
+import CString
+#endif
 #endif
 
 main = do
@@ -41,7 +54,9 @@ main = do
 data Flag 
   = Config FilePath
   | Input FilePath
-  | List | Add Bool {- True => replace existing info -}
+  | List
+  | ListLocal
+  | Add Bool {- True => replace existing info -}
   | Remove String | Show String 
   | Field String | AutoGHCiLibs | Force
   deriving (Eq)
@@ -59,7 +74,9 @@ flags = [
   Option ['f'] ["config-file"] (ReqArg Config "FILE")
        "Use the specified package config file",
   Option ['l'] ["list-packages"] (NoArg List)
-       "List the currently installed packages",
+       "List packages in all config files",
+  Option ['L'] ["list-local-packages"] (NoArg ListLocal)
+       "List packages in the specified config file",
   Option ['a'] ["add-package"] (NoArg (Add False))
        "Add a new package",
   Option ['u'] ["update-package"] (NoArg (Add True))
@@ -78,23 +95,16 @@ flags = [
        "Automatically build libs for GHCi (with -a)"
   ]
 
-#ifdef mingw32_HOST_OS
-subst a b ls = map (\ x -> if x == a then b else x) ls
-
-unDosifyPath xs = subst '\\' '/' xs
-#endif
 
 runit clis = do
-  conf_file <- 
+  let err_msg = "missing -f option, location of package.conf unknown"
+  conf_filenames <- 
      case [ f | Config f <- clis ] of
-        fs@(_:_)  -> return (last fs)
-#ifndef mingw32_HOST_OS
-       [] -> die "missing -f option, location of package.conf unknown"
-#else
-       [] -> do h <- getModuleHandle Nothing
-                n <- getModuleFileName h
-                return (reverse (drop (length "/bin/ghc-pkg.exe") (reverse (unDosifyPath n))) ++ "/package.conf")
-#endif
+        fs@(_:_) -> return (reverse fs) -- NOTE reverse
+       [] -> do mb_dir <- getExecDir "/bin/ghc-pkg.exe"
+                case mb_dir of
+                       Nothing  -> die err_msg
+                       Just dir -> return [dir ++ "/package.conf"]
 
   let toField "import_dirs"     = return import_dirs
       toField "source_dirs"     = return source_dirs
@@ -113,9 +123,17 @@ runit clis = do
 
   fields <- mapM toField [ f | Field f <- clis ]
 
-  s <- readFile conf_file
-  let packages = parsePackageConfig s
-  eval_catch packages (\_ -> die "parse error in package config file")
+  let read_parse_conf filename = do
+         str <- readFile filename
+         let packages = parsePackageConfig str
+         eval_catch packages
+           (\_ -> die (filename ++ ": parse error in package config file"))
+
+  pkg_confs <- mapM read_parse_conf conf_filenames
+
+  let conf_filename = head conf_filenames
+       -- this is the file we're going to update: the last one specified
+       -- on the command-line.
 
   let auto_ghci_libs = any isAuto clis 
         where isAuto AutoGHCiLibs = True; isAuto _ = False
@@ -124,34 +142,43 @@ runit clis = do
       force = Force `elem` clis
 
   case [ c | c <- clis, isAction c ] of
-    [ List ]     -> listPackages packages
-    [ Add upd ]  -> addPackage packages conf_file input_file 
+    [ List ]      -> listPackages pkg_confs conf_filenames
+    [ ListLocal ] -> listPackages [head pkg_confs] [""]
+    [ Add upd ]  -> addPackage pkg_confs conf_filename input_file 
                        auto_ghci_libs upd force
-    [ Remove p ] -> removePackage packages conf_file p
-    [ Show p ]   -> showPackage packages conf_file p fields
+    [ Remove p ] -> removePackage pkg_confs conf_filename p
+    [ Show p ]   -> showPackage pkg_confs conf_filename p fields
     _            -> die (usageInfo usageHeader flags)
 
 
-listPackages :: [PackageConfig] -> IO ()
-listPackages packages = hPutStrLn stdout (listPkgs packages)
+listPackages :: [[PackageConfig]] -> [FilePath] -> IO ()
+listPackages pkg_confs conf_filenames = do
+  zipWithM_ show_pkgconf pkg_confs conf_filenames
+  where show_pkgconf pkg_conf filename =
+         hPutStrLn stdout (render $
+               if null filename 
+                       then packages   
+                       else text (filename ++ ":") $$ nest 4 packages
+               )
+          where packages = fsep (punctuate comma (map (text . name) pkg_conf))
 
-showPackage :: [PackageConfig]
+showPackage :: [[PackageConfig]]
            -> FilePath
            -> String
            -> [PackageConfig -> [String]]
            -> IO ()
-showPackage packages pkgconf pkg_name fields =
-  case [ p | p <- packages, name p == pkg_name ] of
+showPackage pkg_confs filename pkg_name fields =
+  case [ p | pkgs <- pkg_confs, p <- pkgs, name p == pkg_name ] of
     []    -> die ("can't find package `" ++ pkg_name ++ "'")
     [pkg] | null fields -> hPutStrLn stdout (render (dumpPkgGuts pkg))
          | otherwise   -> hPutStrLn stdout (render (vcat 
-                               (map (vcat . map text) (map ($pkg) fields))))
+                               (map (vcat . map text) (map ($ pkg) fields))))
     _     -> die "showPackage: internal error"
 
-addPackage :: [PackageConfig] -> FilePath -> FilePath
+addPackage :: [[PackageConfig]] -> FilePath -> FilePath
         -> Bool -> Bool -> Bool -> IO ()
-addPackage packages pkgconf inputFile auto_ghci_libs updatePkg force = do
-  checkConfigAccess pkgconf
+addPackage pkg_confs filename inputFile auto_ghci_libs updatePkg force = do
+  checkConfigAccess filename
   s <-
     case inputFile of
       "-" -> do
@@ -163,62 +190,62 @@ addPackage packages pkgconf inputFile auto_ghci_libs updatePkg force = do
   let new_pkg = parseOnePackageConfig s
   eval_catch new_pkg (\_ -> die "parse error in package info")
   hPutStrLn stdout "done."
-  hPutStr stdout "Expanding embedded variables..."
+  hPutStr stdout "Expanding embedded variables... "
   new_exp_pkg <- expandEnvVars new_pkg force
   hPutStrLn stdout "done."
-  new_details <- validatePackageConfig new_exp_pkg packages 
+  new_details <- validatePackageConfig new_exp_pkg pkg_confs 
                        auto_ghci_libs updatePkg force
-  savePackageConfig pkgconf
-  maybeRestoreOldConfig pkgconf $
-    writeNewConfig pkgconf new_details
+  savePackageConfig filename
+  maybeRestoreOldConfig filename $
+    writeNewConfig filename new_details
 
-removePackage :: [PackageConfig] -> FilePath -> String -> IO ()
-removePackage packages pkgconf pkgName = do  
-  checkConfigAccess pkgconf
+removePackage :: [[PackageConfig]] -> FilePath -> String -> IO ()
+removePackage (packages : _) filename pkgName = do  
+  checkConfigAccess filename
   when (pkgName `notElem` map name packages)
-       (die ("package `" ++ pkgName ++ "' not installed"))
-  savePackageConfig pkgconf
-  maybeRestoreOldConfig pkgconf $
-    writeNewConfig pkgconf (filter ((/= pkgName) . name) packages)
+       (die (filename ++ ": package `" ++ pkgName ++ "' not found"))
+  savePackageConfig filename
+  maybeRestoreOldConfig filename $
+    writeNewConfig filename (filter ((/= pkgName) . name) packages)
 
 checkConfigAccess :: FilePath -> IO ()
-checkConfigAccess pkgconf = do
-  access <- getPermissions pkgconf
+checkConfigAccess filename = do
+  access <- getPermissions filename
   when (not (writable access))
-      (die "you don't have permission to modify the package configuration file")
+      (die (filename ++ ": you don't have permission to modify this file"))
 
-maybeRestoreOldConfig :: String -> IO () -> IO ()
-maybeRestoreOldConfig conf_file io
+maybeRestoreOldConfig :: FilePath -> IO () -> IO ()
+maybeRestoreOldConfig filename io
   = my_catch 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... "
-       renameFile (conf_file ++ ".old")  conf_file
+       renameFile (filename ++ ".old")  filename
         hPutStrLn stdout "done."
        my_throw e
     )
 
-writeNewConfig :: String -> [PackageConfig] -> IO ()
-writeNewConfig conf_file packages = do
+writeNewConfig :: FilePath -> [PackageConfig] -> IO ()
+writeNewConfig filename packages = do
   hPutStr stdout "Writing new package config file... "
-  h <- openFile conf_file WriteMode
+  h <- openFile filename WriteMode
   hPutStrLn h (dumpPackages packages)
   hClose h
   hPutStrLn stdout "done."
 
-savePackageConfig :: String -> IO ()
-savePackageConfig conf_file = do
+savePackageConfig :: FilePath -> IO ()
+savePackageConfig filename = 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...
-  let oldFile = conf_file ++ ".old"
+  let oldFile = filename ++ ".old"
   doesExist <- doesFileExist oldFile  `catch` (\ _ -> return False)
   when doesExist (removeFile oldFile `catch` (const $ return ()))
-  catch (renameFile conf_file oldFile)
+  catch (renameFile filename oldFile)
        (\ err -> do
                hPutStrLn stderr (unwords [ "Unable to rename "
-                                         , show conf_file
+                                         , show filename
                                          , " to "
                                          , show oldFile
                                          ])
@@ -230,15 +257,15 @@ savePackageConfig conf_file = do
 -- if requested.
 
 validatePackageConfig :: PackageConfig 
-                     -> [PackageConfig]
+                     -> [[PackageConfig]]
                      -> Bool
                      -> Bool
                      -> Bool
                      -> IO [PackageConfig]
-validatePackageConfig pkg pkgs auto_ghci_libs updatePkg force = do
+validatePackageConfig pkg pkg_confs@(pkgs:_) auto_ghci_libs updatePkg force = do
   when (not updatePkg && (name pkg `elem` map name pkgs))
        (die ("package `" ++ name pkg ++ "' is already installed"))
-  mapM_        (checkDep pkgs force) (package_deps pkg)
+  mapM_        (checkDep pkg_confs force) (package_deps pkg)
   mapM_        (checkDir force) (import_dirs pkg)
   mapM_        (checkDir force) (source_dirs pkg)
   mapM_        (checkDir force) (library_dirs pkg)
@@ -260,10 +287,12 @@ checkDir force d
    when (not there)
        (dieOrForce force ("`" ++ d ++ "' doesn't exist or isn't a directory"))
 
-checkDep :: [PackageConfig] -> Bool -> String -> IO ()
+checkDep :: [[PackageConfig]] -> Bool -> String -> IO ()
 checkDep pkgs force n
-  | n `elem` map name pkgs = return ()
+  | n `elem` pkg_names = return ()
   | otherwise = dieOrForce force ("dependency `" ++ n ++ "' doesn't exist")
+  where
+    pkg_names = concat (map (map name) pkgs)
 
 checkHSLib :: [String] -> Bool -> Bool -> String -> IO ()
 checkHSLib dirs auto_ghci_libs force lib = do
@@ -298,8 +327,13 @@ autoBuildGHCiLib dir batch_file ghci_file = do
   let ghci_lib_file  = dir ++ '/':ghci_file
       batch_lib_file = dir ++ '/':batch_file
   hPutStr stderr ("building GHCi library `" ++ ghci_lib_file ++ "'...")
+#ifdef darwin_TARGET_OS
+  system("ld -r -x -o " ++ ghci_lib_file ++ 
+        " -all_load " ++ batch_lib_file)
+#else
   system("ld -r -x -o " ++ ghci_lib_file ++ 
         " --whole-archive " ++ batch_lib_file)
+#endif
   hPutStrLn stderr (" done.")
 
 -----------------------------------------------------------------------------
@@ -348,7 +382,7 @@ expandEnvVars pkg force = do
           (nm,_:remainder) -> do
              nm'  <- lookupEnvVar nm
              str' <- expandString remainder
-             return (nm' ++ str')
+             return (xs ++ nm' ++ str')
           _ -> return str -- no closing '}'
        _ -> return str    
 
@@ -389,3 +423,32 @@ my_catch = Exception.catchAllIO
 #endif
 
 #endif
+
+-----------------------------------------
+--     Cut and pasted from ghc/compiler/SysTools
+
+#if defined(mingw32_HOST_OS)
+subst a b ls = map (\ x -> if x == a then b else x) ls
+unDosifyPath xs = subst '\\' '/' xs
+
+getExecDir :: String -> IO (Maybe String)
+-- (getExecDir cmd) returns the directory in which the current
+--                 executable, which should be called 'cmd', is running
+-- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
+-- you'll get "/a/b/c" back as the result
+getExecDir cmd
+  = allocaArray len $ \buf -> do
+       ret <- getModuleFileName nullPtr buf len
+       if ret == 0 then return Nothing
+                   else do s <- peekCString buf
+                           return (Just (reverse (drop (length cmd) 
+                                                       (reverse (unDosifyPath s)))))
+  where
+    len = 2048::Int -- Plenty, PATH_MAX is 512 under Win32.
+
+foreign import stdcall "GetModuleFileNameA" unsafe 
+  getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
+#else
+getExecDir :: String -> IO (Maybe String) 
+getExecDir s = do return Nothing
+#endif