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