[project @ 2004-08-13 13:04:50 by simonmar]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
1 {-# OPTIONS -fglasgow-exts #-}
2
3 -----------------------------------------------------------------------------
4 -- Package management tool
5 -----------------------------------------------------------------------------
6
7 module Main where
8
9 import Package
10
11 #if __GLASGOW_HASKELL__ >= 504
12 import System.Console.GetOpt
13 import Text.PrettyPrint
14 import qualified Control.Exception as Exception
15 #else
16 import GetOpt
17 import Pretty
18 import qualified Exception
19 #endif
20
21 import Monad
22 import Directory
23 import System   ( getEnv, getArgs, getProgName,
24                   system, exitWith,
25                   ExitCode(..)
26                 )
27 import IO
28 import List ( isPrefixOf, isSuffixOf )
29
30 import ParsePkgConfLite
31
32 #include "../../includes/ghcconfig.h"
33
34 #ifdef mingw32_HOST_OS
35 import Foreign
36
37 #if __GLASGOW_HASKELL__ >= 504
38 import Foreign.C.String
39 #else
40 import CString
41 #endif
42 #endif
43
44 main :: IO ()
45 main = do
46   args <- getArgs
47
48   case getOpt Permute flags args of
49         (cli,_,[]) | DumpHelp `elem` cli -> do
50            prog <- getProgramName
51            bye (usageInfo (usageHeader prog) flags)
52         (cli,_,[]) | DumpVersion `elem` cli ->
53            bye copyright
54         (cli@(_:_),[],[]) ->
55            runit cli
56         (_,_,errors) -> do
57            prog <- getProgramName
58            die (concat errors ++ usageInfo (usageHeader prog) flags)
59
60 data Flag 
61   = Config FilePath
62   | Input FilePath
63   | List
64   | ListLocal
65   | Add Bool {- True => replace existing info -}
66   | Remove String | Show String 
67   | Field String | AutoGHCiLibs | Force
68   | DefinedName String String
69   | DumpHelp
70   | DumpVersion
71   deriving (Eq)
72
73 isAction :: Flag -> Bool
74 isAction (Config _)     = False
75 isAction (Field _)      = False
76 isAction (Input _)      = False
77 isAction (AutoGHCiLibs) = False
78 isAction (Force)        = False
79 isAction DefinedName{}  = False
80 isAction _              = True
81
82 copyright :: String
83 copyright = "GHC package manager version " ++ version ++ "\n"
84
85 -- hackery to convice cpp to splice GHC_PKG_VERSION into a string
86 version :: String
87 version = GHC_PKG_VERSION
88
89 usageHeader :: String -> String
90 usageHeader prog = "Usage: " ++ prog ++ " [OPTION...]\n"
91
92 flags :: [OptDescr Flag]
93 flags = [
94   Option ['f'] ["config-file"] (ReqArg Config "FILE")
95         "use the specified package config file",
96   Option ['l'] ["list-packages"] (NoArg List)
97         "list packages in all config files",
98   Option ['L'] ["list-local-packages"] (NoArg ListLocal)
99         "list packages in the specified config file",
100   Option ['a'] ["add-package"] (NoArg (Add False))
101         "add a new package",
102   Option ['u'] ["update-package"] (NoArg (Add True))
103         "update package with new configuration",
104   Option ['i'] ["input-file"] (ReqArg Input "FILE")
105         "read new package info from specified file",
106   Option ['s'] ["show-package"] (ReqArg Show "NAME")
107         "show the configuration for package NAME",
108   Option [] ["field"] (ReqArg Field "FIELD")
109         "(with --show-package) Show field FIELD only",
110   Option [] ["force"] (NoArg Force)
111         "ignore missing directories/libraries",
112   Option ['r'] ["remove-package"] (ReqArg Remove "NAME")
113         "remove an installed package",
114   Option ['g'] ["auto-ghci-libs"] (NoArg AutoGHCiLibs)
115         "automatically build libs for GHCi (with -a)",
116   Option ['D'] ["define-name"] (ReqArg toDefined "NAME=VALUE")
117         "define NAME as VALUE",
118    Option ['?'] ["help"] (NoArg DumpHelp)
119         "display this help and exit",
120    Option ['V'] ["version"] (NoArg DumpVersion)
121         "output version information and exit"
122   ]
123  where
124   toDefined str = 
125     case break (=='=') str of
126       (nm,[]) -> DefinedName nm []
127       (nm,_:val) -> DefinedName nm val
128
129 runit :: [Flag] -> IO ()
130 runit clis = do
131   let err_msg = "missing -f option, location of package.conf unknown\n"
132   conf_filenames <- 
133      case [ f | Config f <- clis ] of
134         fs@(_:_) -> return (reverse fs) -- NOTE reverse
135         [] -> do mb_dir <- getExecDir "/bin/ghc-pkg.exe"
136                  case mb_dir of
137                         Nothing  -> die err_msg
138                         Just dir -> return [dir ++ "/package.conf"]
139
140   let toField "import_dirs"     = return import_dirs
141       toField "source_dirs"     = return source_dirs
142       toField "library_dirs"    = return library_dirs
143       toField "hs_libraries"    = return hs_libraries
144       toField "extra_libraries" = return extra_libraries
145       toField "include_dirs"    = return include_dirs
146       toField "c_includes"      = return c_includes
147       toField "package_deps"    = return package_deps
148       toField "extra_ghc_opts"  = return extra_ghc_opts
149       toField "extra_cc_opts"   = return extra_cc_opts
150       toField "extra_ld_opts"   = return extra_ld_opts  
151       toField "framework_dirs"  = return framework_dirs  
152       toField "extra_frameworks"= return extra_frameworks  
153       toField s                 = die ("unknown field: `" ++ s ++ "'\n")
154
155   fields <- mapM toField [ f | Field f <- clis ]
156
157   let read_parse_conf filename = do
158           str <- readFile filename
159           let packages = parsePackageConfig str
160           eval_catch packages
161             (\_ -> die (filename ++ ": parse error in package config file\n"))
162
163   pkg_confs <- mapM read_parse_conf conf_filenames
164
165   let conf_filename = head conf_filenames
166         -- this is the file we're going to update: the last one specified
167         -- on the command-line.
168
169   let auto_ghci_libs = any isAuto clis 
170          where isAuto AutoGHCiLibs = True; isAuto _ = False
171       input_file = head ([ f | (Input f) <- clis] ++ ["-"])
172
173       force = Force `elem` clis
174       
175       defines = [ (nm,val) | DefinedName nm val <- clis ]
176
177   case [ c | c <- clis, isAction c ] of
178     [ List ]      -> listPackages pkg_confs conf_filenames
179     [ ListLocal ] -> listPackages [head pkg_confs] [""]
180     [ Add upd ]  -> addPackage pkg_confs defines 
181                                conf_filename input_file
182                                auto_ghci_libs upd force
183     [ Remove p ] -> removePackage pkg_confs conf_filename p
184     [ Show p ]   -> showPackage pkg_confs conf_filename p fields
185     _            -> do prog <- getProgramName
186                        die (usageInfo (usageHeader prog) flags)
187
188
189 listPackages :: [[PackageConfig]] -> [FilePath] -> IO ()
190 listPackages pkg_confs conf_filenames = do
191   zipWithM_ show_pkgconf pkg_confs conf_filenames
192   where show_pkgconf pkg_conf filename =
193           hPutStrLn stdout (render $
194                 if null filename 
195                         then packages   
196                         else text (filename ++ ":") $$ nest 4 packages
197                 )
198            where packages = fsep (punctuate comma (map (text . name) pkg_conf))
199
200 showPackage :: [[PackageConfig]]
201             -> FilePath
202             -> String
203             -> [PackageConfig -> [String]]
204             -> IO ()
205 showPackage pkg_confs _ pkg_name fields =
206   case [ p | pkgs <- pkg_confs, p <- pkgs, name p == pkg_name ] of
207     []    -> die ("can't find package `" ++ pkg_name ++ "'\n")
208     [pkg] | null fields -> hPutStrLn stdout (render (dumpPkgGuts pkg))
209           | otherwise   -> hPutStrLn stdout (render (vcat 
210                                 (map (vcat . map text) (map ($ pkg) fields))))
211     _     -> die "showPackage: internal error\n"
212
213 addPackage :: [[PackageConfig]] -> [(String, String)] 
214            -> FilePath -> FilePath
215            -> Bool -> Bool -> Bool -> IO ()
216 addPackage pkg_confs defines 
217            filename inputFile
218            auto_ghci_libs updatePkg force = do
219   checkConfigAccess filename
220   s <-
221     case inputFile of
222       "-" -> do
223         hPutStr stdout "Reading package info from stdin... "
224         getContents
225       f   -> do
226         hPutStr stdout ("Reading package info from " ++ show f)
227         readFile f
228   let new_pkg = parseOnePackageConfig s
229   eval_catch new_pkg (\_ -> die "parse error in package info\n")
230   hPutStrLn stdout "done."
231   hPutStr stdout "Expanding embedded variables... "
232   new_exp_pkg <- expandEnvVars new_pkg defines force
233   hPutStrLn stdout "done."
234   new_details <- validatePackageConfig new_exp_pkg pkg_confs 
235                         auto_ghci_libs updatePkg force
236   savePackageConfig filename
237   maybeRestoreOldConfig filename $
238     writeNewConfig filename new_details
239
240 removePackage :: [[PackageConfig]] -> FilePath -> String -> IO ()
241 removePackage (packages : _) filename pkgName = do  
242   checkConfigAccess filename
243   when (pkgName `notElem` map name packages)
244        (die (filename ++ ": package `" ++ pkgName ++ "' not found\n"))
245   savePackageConfig filename
246   maybeRestoreOldConfig filename $
247     writeNewConfig filename (filter ((/= pkgName) . name) packages)
248
249 checkConfigAccess :: FilePath -> IO ()
250 checkConfigAccess filename = do
251   access <- getPermissions filename
252   when (not (writable access))
253       (die (filename ++ ": you don't have permission to modify this file\n"))
254
255 maybeRestoreOldConfig :: FilePath -> IO () -> IO ()
256 maybeRestoreOldConfig filename io
257   = my_catch io (\e -> do
258         hPutStr stdout ("\nWARNING: an error was encountered while the new \n"++
259                           "configuration was being written.  Attempting to \n"++
260                           "restore the old configuration... ")
261         renameFile (filename ++ ".old")  filename
262         hPutStrLn stdout "done."
263         my_throw e
264     )
265
266 writeNewConfig :: FilePath -> [PackageConfig] -> IO ()
267 writeNewConfig filename packages = do
268   hPutStr stdout "Writing new package config file... "
269   h <- openFile filename WriteMode
270   hPutStrLn h (dumpPackages packages)
271   hClose h
272   hPutStrLn stdout "done."
273
274 savePackageConfig :: FilePath -> IO ()
275 savePackageConfig filename = do
276   hPutStr stdout "Saving old package config file... "
277     -- mv rather than cp because we've already done an hGetContents
278     -- on this file so we won't be able to open it for writing
279     -- unless we move the old one out of the way...
280   let oldFile = filename ++ ".old"
281   doesExist <- doesFileExist oldFile  `catch` (\ _ -> return False)
282   when doesExist (removeFile oldFile `catch` (const $ return ()))
283   catch (renameFile filename oldFile)
284         (\ err -> do
285                 hPutStrLn stderr (unwords [ "Unable to rename "
286                                           , show filename
287                                           , " to "
288                                           , show oldFile
289                                           ])
290                 ioError err)
291   hPutStrLn stdout "done."
292
293 -----------------------------------------------------------------------------
294 -- Sanity-check a new package config, and automatically build GHCi libs
295 -- if requested.
296
297 validatePackageConfig :: PackageConfig 
298                       -> [[PackageConfig]]
299                       -> Bool
300                       -> Bool
301                       -> Bool
302                       -> IO [PackageConfig]
303 validatePackageConfig pkg pkg_confs@(pkgs:_) auto_ghci_libs updatePkg force = do
304   when (not updatePkg && (name pkg `elem` map name pkgs))
305        (die ("package `" ++ name pkg ++ "' is already installed\n"))
306   mapM_ (checkDep pkg_confs force) (package_deps pkg)
307   mapM_ (checkDir force) (import_dirs pkg)
308   mapM_ (checkDir force) (source_dirs pkg)
309   mapM_ (checkDir force) (library_dirs pkg)
310   mapM_ (checkDir force) (include_dirs pkg)
311   mapM_ (checkHSLib (library_dirs pkg) auto_ghci_libs force) (hs_libraries pkg)
312   -- ToDo: check these somehow?
313   --    extra_libraries :: [String],
314   --    c_includes      :: [String],
315   let existing_pkgs
316        | updatePkg = filter ((/=(name pkg)).name) pkgs  
317        | otherwise = pkgs
318   return (existing_pkgs ++ [pkg])
319
320 checkDir :: Bool -> String -> IO ()
321 checkDir force d
322  | "$libdir" `isPrefixOf` d = return ()
323         -- can't check this, because we don't know what $libdir is
324  | otherwise = do
325    there <- doesDirectoryExist d
326    when (not there)
327        (dieOrForce force ("`" ++ d ++ "' doesn't exist or isn't a directory\n"))
328
329 checkDep :: [[PackageConfig]] -> Bool -> String -> IO ()
330 checkDep pkgs force n
331   | n `elem` pkg_names = return ()
332   | otherwise = dieOrForce force ("dependency `" ++ n ++ "' doesn't exist\n")
333   where
334     pkg_names = concat (map (map name) pkgs)
335
336 checkHSLib :: [String] -> Bool -> Bool -> String -> IO ()
337 checkHSLib dirs auto_ghci_libs force lib = do
338   let batch_lib_file = "lib" ++ lib ++ ".a"
339   bs <- mapM (doesLibExistIn batch_lib_file) dirs
340   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
341         [] -> dieOrForce force ("cannot find `" ++ batch_lib_file ++
342                                  "' on library path") 
343         (dir:_) -> checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
344
345 doesLibExistIn :: String -> String -> IO Bool
346 doesLibExistIn lib d
347  | "$libdir" `isPrefixOf` d = return True
348  | otherwise                = doesFileExist (d ++ '/':lib)
349
350 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
351 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build
352   | auto_build = autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
353   | otherwise  = do
354       bs <- mapM (doesLibExistIn ghci_lib_file) dirs
355       case [dir | (exists,dir) <- zip bs dirs, exists] of
356         []    -> hPutStrLn stderr ("warning: can't find GHCi lib `" ++ ghci_lib_file ++ "'")
357         (_:_) -> return ()
358   where
359     ghci_lib_file = lib ++ ".o"
360
361 -- automatically build the GHCi version of a batch lib, 
362 -- using ld --whole-archive.
363
364 autoBuildGHCiLib :: String -> String -> String -> IO ()
365 autoBuildGHCiLib dir batch_file ghci_file = do
366   let ghci_lib_file  = dir ++ '/':ghci_file
367       batch_lib_file = dir ++ '/':batch_file
368   hPutStr stderr ("building GHCi library `" ++ ghci_lib_file ++ "'...")
369 #ifdef darwin_TARGET_OS
370   system("ld -r -x -o " ++ ghci_lib_file ++ 
371          " -all_load " ++ batch_lib_file)
372 #else
373 #ifdef mingw32_HOST_OS
374   execDir <- getExecDir "/bin/ghc-pkg.exe"
375   system (maybe "" (++"/gcc-lib/") execDir++"ld -r -x -o " ++ ghci_lib_file ++ 
376          " --whole-archive " ++ batch_lib_file)
377 #else
378   system("ld -r -x -o " ++ ghci_lib_file ++ 
379          " --whole-archive " ++ batch_lib_file)
380 #endif
381 #endif
382   hPutStrLn stderr (" done.")
383
384 -----------------------------------------------------------------------------
385 expandEnvVars :: PackageConfig -> [(String, String)] -> Bool -> IO PackageConfig
386 expandEnvVars pkg defines force = do
387    -- permit _all_ strings to contain ${..} environment variable references,
388    -- arguably too flexible.
389   nm       <- expandString (name pkg)
390   imp_dirs <- expandStrings (import_dirs pkg) 
391   src_dirs <- expandStrings (source_dirs pkg) 
392   lib_dirs <- expandStrings (library_dirs pkg) 
393   hs_libs  <- expandStrings (hs_libraries pkg)
394   ex_libs  <- expandStrings (extra_libraries pkg)
395   inc_dirs <- expandStrings (include_dirs pkg)
396   c_incs   <- expandStrings (c_includes pkg)
397   p_deps   <- expandStrings (package_deps pkg)
398   e_g_opts <- expandStrings (extra_ghc_opts pkg)
399   e_c_opts <- expandStrings (extra_cc_opts pkg)
400   e_l_opts <- expandStrings (extra_ld_opts pkg)
401   f_dirs   <- expandStrings (framework_dirs pkg)
402   e_frames <- expandStrings (extra_frameworks pkg)
403   return (pkg { name            = nm
404               , import_dirs     = imp_dirs
405               , source_dirs     = src_dirs
406               , library_dirs    = lib_dirs
407               , hs_libraries    = hs_libs
408               , extra_libraries = ex_libs
409               , include_dirs    = inc_dirs
410               , c_includes      = c_incs
411               , package_deps    = p_deps
412               , extra_ghc_opts  = e_g_opts
413               , extra_cc_opts   = e_c_opts
414               , extra_ld_opts   = e_l_opts
415               , framework_dirs  = f_dirs
416               , extra_frameworks= e_frames
417               })
418   where
419    expandStrings :: [String] -> IO [String]
420    expandStrings = liftM concat . mapM expandSpecial
421
422    -- Permit substitutions for list-valued variables (but only when
423    -- they occur alone), e.g., package_deps["${deps}"] where env var
424    -- (say) 'deps' is "base,haskell98,network"
425    expandSpecial :: String -> IO [String]
426    expandSpecial str =
427       let expand f = liftM f $ expandString str
428       in case splitString str of
429          [Var _] -> expand (wordsBy (== ','))
430          _ -> expand (\x -> [x])
431
432    expandString :: String -> IO String
433    expandString = liftM concat . mapM expandElem . splitString
434
435    expandElem :: Elem -> IO String
436    expandElem (String s) = return s
437    expandElem (Var v)    = lookupEnvVar v
438
439    lookupEnvVar :: String -> IO String
440    lookupEnvVar nm = 
441      case lookup nm defines of
442        Just x | not (null x) -> return x
443        _      -> 
444         catch (System.getEnv nm)
445            (\ _ -> do dieOrForce force ("Unable to expand variable " ++ 
446                                         show nm)
447                       return "")
448
449 data Elem = String String | Var String
450
451 splitString :: String -> [Elem]
452 splitString "" = []
453 splitString str =
454    case break (== '$') str of
455       (pre, _:'{':xs) ->
456          case span (/= '}') xs of
457             (var, _:suf) ->
458                (if null pre then id else (String pre :)) (Var var : splitString suf)
459             _ -> [String str]   -- no closing brace
460       _ -> [String str]   -- no dollar/opening brace combo
461
462 -- wordsBy isSpace == words
463 wordsBy :: (Char -> Bool) -> String -> [String]
464 wordsBy p s = case dropWhile p s of
465   "" -> []
466   s' -> w : wordsBy p s'' where (w,s'') = break p s'
467
468 -----------------------------------------------------------------------------
469
470 getProgramName :: IO String
471 getProgramName = liftM (`withoutSuffix` ".bin") getProgName
472    where str `withoutSuffix` suff
473             | suff `isSuffixOf` str = take (length str - length suff) str
474             | otherwise             = str
475
476 bye :: String -> IO a
477 bye s = putStr s >> exitWith ExitSuccess
478
479 die :: String -> IO a
480 die s = do { hFlush stdout ; hPutStr stderr s; exitWith (ExitFailure 1) }
481
482 dieOrForce :: Bool -> String -> IO ()
483 dieOrForce force s 
484   | force     = do hFlush stdout; hPutStrLn stderr (s ++ " (ignoring)")
485   | otherwise = die (s ++ "\n")
486
487 -----------------------------------------------------------------------------
488 -- Exceptions
489
490 #ifndef __GLASGOW_HASKELL__
491
492 eval_catch a h = a `seq` return ()
493 my_catch = IO.catch
494 my_throw = IO.fail
495
496 #else /* GHC */
497
498 my_throw = Exception.throw
499 #if __GLASGOW_HASKELL__ > 408
500 eval_catch = Exception.catch . Exception.evaluate
501 my_catch = Exception.catch
502 #else
503 eval_catch = Exception.catchAll
504 my_catch = Exception.catchAllIO
505 #endif
506
507 #endif
508
509 -----------------------------------------
510 --      Cut and pasted from ghc/compiler/SysTools
511
512 #if defined(mingw32_HOST_OS)
513 subst a b ls = map (\ x -> if x == a then b else x) ls
514 unDosifyPath xs = subst '\\' '/' xs
515
516 getExecDir :: String -> IO (Maybe String)
517 -- (getExecDir cmd) returns the directory in which the current
518 --                  executable, which should be called 'cmd', is running
519 -- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
520 -- you'll get "/a/b/c" back as the result
521 getExecDir cmd
522   = allocaArray len $ \buf -> do
523         ret <- getModuleFileName nullPtr buf len
524         if ret == 0 then return Nothing
525                     else do s <- peekCString buf
526                             return (Just (reverse (drop (length cmd) 
527                                                         (reverse (unDosifyPath s)))))
528   where
529     len = 2048::Int -- Plenty, PATH_MAX is 512 under Win32.
530
531 foreign import stdcall "GetModuleFileNameA" unsafe 
532   getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
533 #else
534 getExecDir :: String -> IO (Maybe String) 
535 getExecDir _ = return Nothing
536 #endif