[project @ 2002-10-29 10:53:42 by simonpj]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
index 64cd807..5bef564 100644 (file)
@@ -1,5 +1,7 @@
+{-# OPTIONS -fglasgow-exts #-}
+
 -----------------------------------------------------------------------------
--- $Id: Main.hs,v 1.21 2002/02/12 15:17:24 simonmar Exp $
+-- $Id: Main.hs,v 1.31 2002/10/29 10:53:42 simonpj 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, 
@@ -22,10 +29,18 @@ import System       ( getEnv, getArgs,
 import IO
 import List ( isPrefixOf )
 
+import ParsePkgConfLite
+
 #include "../../includes/config.h"
 
-#ifdef mingw32_TARGET_OS
-import Win32DLL
+#ifdef mingw32_HOST_OS
+import Foreign
+
+#if __GLASGOW_HASKELL__ >= 504
+import Foreign.C.String
+#else
+import CString
+#endif
 #endif
 
 main = do
@@ -41,12 +56,14 @@ data Flag
   | Input FilePath
   | List | Add Bool {- True => replace existing info -}
   | Remove String | Show String 
-  | Field String | AutoGHCiLibs
+  | Field String | AutoGHCiLibs | Force
+  deriving (Eq)
 
 isAction (Config _)     = False
 isAction (Field _)      = False
 isAction (Input _)      = False
 isAction (AutoGHCiLibs) = False
+isAction (Force)       = False
 isAction _              = True
 
 usageHeader = "ghc-pkg [OPTION...]"
@@ -66,29 +83,24 @@ flags = [
        "Show the configuration for package NAME",
   Option [] ["field"] (ReqArg Field "FIELD")
        "(with --show-package) Show field FIELD only",
+  Option [] ["force"] (NoArg Force)
+       "ignore missing directories/libraries",
   Option ['r'] ["remove-package"] (ReqArg Remove "NAME")
        "Remove an installed package",
   Option ['g'] ["auto-ghci-libs"] (NoArg AutoGHCiLibs)
        "Automatically build libs for GHCi (with -a)"
   ]
 
-#ifdef mingw32_TARGET_OS
-subst a b ls = map (\ x -> if x == a then b else x) ls
-
-unDosifyPath xs = subst '\\' '/' xs
-#endif
 
 runit clis = do
+  let err_msg = "missing -f option, location of package.conf unknown"
   conf_file <- 
      case [ f | Config f <- clis ] of
         fs@(_:_)  -> return (last fs)
-#ifndef mingw32_TARGET_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
+       [] -> 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
@@ -101,21 +113,26 @@ runit clis = do
       toField "extra_ghc_opts"  = return extra_ghc_opts
       toField "extra_cc_opts"   = return extra_cc_opts
       toField "extra_ld_opts"   = return extra_ld_opts  
+      toField "framework_dirs"  = return framework_dirs  
+      toField "extra_frameworks"= return extra_frameworks  
       toField s                        = die ("unknown field: `" ++ s ++ "'")
 
   fields <- mapM toField [ f | Field f <- clis ]
 
   s <- readFile conf_file
-  let packages = read s :: [PackageConfig]
+  let packages = parsePackageConfig s
   eval_catch packages (\_ -> die "parse error in package config file")
 
   let auto_ghci_libs = any isAuto clis 
         where isAuto AutoGHCiLibs = True; isAuto _ = False
       input_file = head ([ f | (Input f) <- clis] ++ ["-"])
 
+      force = Force `elem` clis
+
   case [ c | c <- clis, isAction c ] of
     [ List ]     -> listPackages packages
-    [ Add upd ]  -> addPackage packages conf_file input_file auto_ghci_libs upd
+    [ Add upd ]  -> addPackage packages conf_file input_file 
+                       auto_ghci_libs upd force
     [ Remove p ] -> removePackage packages conf_file p
     [ Show p ]   -> showPackage packages conf_file p fields
     _            -> die (usageInfo usageHeader flags)
@@ -134,11 +151,12 @@ showPackage packages pkgconf pkg_name fields =
     []    -> 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 -> Bool -> Bool -> IO ()
-addPackage packages pkgconf inputFile auto_ghci_libs updatePkg = do
+addPackage :: [PackageConfig] -> FilePath -> FilePath
+        -> Bool -> Bool -> Bool -> IO ()
+addPackage packages pkgconf inputFile auto_ghci_libs updatePkg force = do
   checkConfigAccess pkgconf
   s <-
     case inputFile of
@@ -148,13 +166,14 @@ addPackage packages pkgconf inputFile auto_ghci_libs updatePkg = do
       f   -> do
         hPutStr stdout ("Reading package info from " ++ show f)
        readFile f
-  let new_pkg = read s :: PackageConfig
+  let new_pkg = parseOnePackageConfig s
   eval_catch new_pkg (\_ -> die "parse error in package info")
   hPutStrLn stdout "done."
   hPutStr stdout "Expanding embedded variables..."
-  new_exp_pkg <- expandEnvVars new_pkg
+  new_exp_pkg <- expandEnvVars new_pkg force
   hPutStrLn stdout "done."
-  new_details <- validatePackageConfig new_exp_pkg packages auto_ghci_libs updatePkg
+  new_details <- validatePackageConfig new_exp_pkg packages 
+                       auto_ghci_libs updatePkg force
   savePackageConfig pkgconf
   maybeRestoreOldConfig pkgconf $
     writeNewConfig pkgconf new_details
@@ -220,16 +239,17 @@ validatePackageConfig :: PackageConfig
                      -> [PackageConfig]
                      -> Bool
                      -> Bool
+                     -> Bool
                      -> IO [PackageConfig]
-validatePackageConfig pkg pkgs auto_ghci_libs updatePkg = do
+validatePackageConfig pkg 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) (package_deps pkg)
-  mapM_        checkDir (import_dirs pkg)
-  mapM_        checkDir (source_dirs pkg)
-  mapM_        checkDir (library_dirs pkg)
-  mapM_        checkDir (include_dirs pkg)
-  mapM_ (checkHSLib (library_dirs pkg) auto_ghci_libs) (hs_libraries pkg)
+  mapM_        (checkDep pkgs force) (package_deps pkg)
+  mapM_        (checkDir force) (import_dirs pkg)
+  mapM_        (checkDir force) (source_dirs pkg)
+  mapM_        (checkDir force) (library_dirs pkg)
+  mapM_        (checkDir force) (include_dirs pkg)
+  mapM_ (checkHSLib (library_dirs pkg) auto_ghci_libs force) (hs_libraries pkg)
   -- ToDo: check these somehow?
   --   extra_libraries :: [String],
   --   c_includes      :: [String],
@@ -238,25 +258,26 @@ validatePackageConfig pkg pkgs auto_ghci_libs updatePkg = do
        | otherwise = pkgs
   return (existing_pkgs ++ [pkg])
 
-checkDir d
+checkDir force d
  | "$libdir" `isPrefixOf` d = return ()
        -- can't check this, because we don't know what $libdir is
  | otherwise = do
    there <- doesDirectoryExist d
    when (not there)
-       (die ("`" ++ d ++ "' doesn't exist or isn't a directory"))
+       (dieOrForce force ("`" ++ d ++ "' doesn't exist or isn't a directory"))
 
-checkDep :: [PackageConfig] -> String -> IO ()
-checkDep pkgs n
+checkDep :: [PackageConfig] -> Bool -> String -> IO ()
+checkDep pkgs force n
   | n `elem` map name pkgs = return ()
-  | otherwise = die ("dependency `" ++ n ++ "' doesn't exist")
+  | otherwise = dieOrForce force ("dependency `" ++ n ++ "' doesn't exist")
 
-checkHSLib :: [String] -> Bool -> String -> IO ()
-checkHSLib dirs auto_ghci_libs lib = do
+checkHSLib :: [String] -> Bool -> Bool -> String -> IO ()
+checkHSLib dirs auto_ghci_libs force lib = do
   let batch_lib_file = "lib" ++ lib ++ ".a"
   bs <- mapM (doesLibExistIn batch_lib_file) dirs
   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
-       [] -> die ("cannot find `" ++ batch_lib_file ++ "' on library path") 
+       [] -> dieOrForce force ("cannot find `" ++ batch_lib_file ++
+                                "' on library path") 
        (dir:_) -> checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
 
 doesLibExistIn lib d
@@ -283,13 +304,18 @@ 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.")
 
 -----------------------------------------------------------------------------
-expandEnvVars :: PackageConfig -> IO PackageConfig
-expandEnvVars pkg = do
+expandEnvVars :: PackageConfig -> Bool -> IO PackageConfig
+expandEnvVars pkg force = do
    -- permit _all_ strings to contain ${..} environment variable references,
    -- arguably too flexible.
   nm       <- expandString (name pkg)
@@ -304,6 +330,8 @@ expandEnvVars pkg = do
   e_g_opts <- expandStrings (extra_ghc_opts pkg)
   e_c_opts <- expandStrings (extra_cc_opts pkg)
   e_l_opts <- expandStrings (extra_ld_opts pkg)
+  f_dirs   <- expandStrings (framework_dirs pkg)
+  e_frames <- expandStrings (extra_frameworks pkg)
   return (pkg { name            = nm
              , import_dirs     = imp_dirs
              , source_dirs     = src_dirs
@@ -316,6 +344,8 @@ expandEnvVars pkg = do
              , extra_ghc_opts  = e_g_opts
              , extra_cc_opts   = e_c_opts
              , extra_ld_opts   = e_l_opts
+             , framework_dirs  = f_dirs
+             , extra_frameworks= e_frames
              })
   where
    expandStrings = mapM expandString
@@ -335,13 +365,20 @@ expandEnvVars pkg = do
 
    lookupEnvVar nm = 
        catch (System.getEnv nm)
-             (\ _ -> die ("Unable to expand variable " ++ show nm))
+          (\ _ -> do dieOrForce force ("Unable to expand variable " ++ 
+                                       show nm)
+                     return "")
 
 -----------------------------------------------------------------------------
 
 die :: String -> IO a
 die s = do { hFlush stdout ; hPutStrLn stderr s; exitWith (ExitFailure 1) }
 
+dieOrForce :: Bool -> String -> IO ()
+dieOrForce force s 
+  | force     = do hFlush stdout; hPutStrLn stderr (s ++ " (ignoring)")
+  | otherwise = die s
+
 -----------------------------------------------------------------------------
 -- Exceptions
 
@@ -363,3 +400,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