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