324e7d9fe5c121690b35727c88777d14785a7475
[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 = do
45   args <- getArgs
46
47   case getOpt Permute flags args of
48         (cli,_,[]) | DumpHelp `elem` cli -> do
49            prog <- getProgramName
50            bye (usageInfo (usageHeader prog) flags)
51         (cli,_,[]) | DumpVersion `elem` cli ->
52            bye copyright
53         (cli@(_:_),[],[]) ->
54            runit cli
55         (_,_,errors) -> do
56            prog <- getProgramName
57            die (concat errors ++ usageInfo (usageHeader prog) flags)
58
59 data Flag 
60   = Config FilePath
61   | Input FilePath
62   | List
63   | ListLocal
64   | Add Bool {- True => replace existing info -}
65   | Remove String | Show String 
66   | Field String | AutoGHCiLibs | Force
67   | DefinedName String String
68   | DumpHelp
69   | DumpVersion
70   deriving (Eq)
71
72 isAction (Config _)     = False
73 isAction (Field _)      = False
74 isAction (Input _)      = False
75 isAction (AutoGHCiLibs) = False
76 isAction (Force)        = False
77 isAction DefinedName{}  = False
78 isAction _              = True
79
80 copyright :: String
81 copyright = "GHC package manager version " ++ version ++ "\n"
82
83 -- hackery to convice cpp to splice GHC_PKG_VERSION into a string
84 version :: String
85 version = tail "\ 
86    \ GHC_PKG_VERSION"
87
88 usageHeader :: String -> String
89 usageHeader prog = "Usage: " ++ prog ++ " [OPTION...]\n"
90
91 flags = [
92   Option ['f'] ["config-file"] (ReqArg Config "FILE")
93         "use the specified package config file",
94   Option ['l'] ["list-packages"] (NoArg List)
95         "list packages in all config files",
96   Option ['L'] ["list-local-packages"] (NoArg ListLocal)
97         "list packages in the specified config file",
98   Option ['a'] ["add-package"] (NoArg (Add False))
99         "add a new package",
100   Option ['u'] ["update-package"] (NoArg (Add True))
101         "update package with new configuration",
102   Option ['i'] ["input-file"] (ReqArg Input "FILE")
103         "read new package info from specified file",
104   Option ['s'] ["show-package"] (ReqArg Show "NAME")
105         "show the configuration for package NAME",
106   Option [] ["field"] (ReqArg Field "FIELD")
107         "(with --show-package) Show field FIELD only",
108   Option [] ["force"] (NoArg Force)
109         "ignore missing directories/libraries",
110   Option ['r'] ["remove-package"] (ReqArg Remove "NAME")
111         "remove an installed package",
112   Option ['g'] ["auto-ghci-libs"] (NoArg AutoGHCiLibs)
113         "automatically build libs for GHCi (with -a)",
114   Option ['D'] ["define-name"] (ReqArg toDefined "NAME=VALUE")
115         "define NAME as VALUE",
116    Option ['?'] ["help"] (NoArg DumpHelp)
117         "display this help and exit",
118    Option ['V'] ["version"] (NoArg DumpVersion)
119         "output version information and exit"
120   ]
121  where
122   toDefined str = 
123     case break (=='=') str of
124       (nm,[]) -> DefinedName nm []
125       (nm,_:val) -> DefinedName nm val
126
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 filename 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 force d
318  | "$libdir" `isPrefixOf` d = return ()
319         -- can't check this, because we don't know what $libdir is
320  | otherwise = do
321    there <- doesDirectoryExist d
322    when (not there)
323        (dieOrForce force ("`" ++ d ++ "' doesn't exist or isn't a directory\n"))
324
325 checkDep :: [[PackageConfig]] -> Bool -> String -> IO ()
326 checkDep pkgs force n
327   | n `elem` pkg_names = return ()
328   | otherwise = dieOrForce force ("dependency `" ++ n ++ "' doesn't exist\n")
329   where
330     pkg_names = concat (map (map name) pkgs)
331
332 checkHSLib :: [String] -> Bool -> Bool -> String -> IO ()
333 checkHSLib dirs auto_ghci_libs force lib = do
334   let batch_lib_file = "lib" ++ lib ++ ".a"
335   bs <- mapM (doesLibExistIn batch_lib_file) dirs
336   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
337         [] -> dieOrForce force ("cannot find `" ++ batch_lib_file ++
338                                  "' on library path") 
339         (dir:_) -> checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
340
341 doesLibExistIn lib d
342  | "$libdir" `isPrefixOf` d = return True
343  | otherwise                = doesFileExist (d ++ '/':lib)
344
345 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
346 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build = do
347   let ghci_lib_file = lib ++ ".o"
348       ghci_lib_path = batch_lib_dir ++ '/':ghci_lib_file
349   bs <- mapM (\d -> doesFileExist (d ++ '/':ghci_lib_file)) dirs
350   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
351         [] | auto_build -> 
352                 autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
353            | otherwise  -> 
354                 hPutStrLn stderr ("warning: can't find GHCi lib `"
355                                          ++ ghci_lib_file ++ "'")
356         (dir:_) -> return ()
357
358 -- automatically build the GHCi version of a batch lib, 
359 -- using ld --whole-archive.
360
361 autoBuildGHCiLib dir batch_file ghci_file = do
362   let ghci_lib_file  = dir ++ '/':ghci_file
363       batch_lib_file = dir ++ '/':batch_file
364   hPutStr stderr ("building GHCi library `" ++ ghci_lib_file ++ "'...")
365 #ifdef darwin_TARGET_OS
366   system("ld -r -x -o " ++ ghci_lib_file ++ 
367          " -all_load " ++ batch_lib_file)
368 #else
369   system("ld -r -x -o " ++ ghci_lib_file ++ 
370          " --whole-archive " ++ batch_lib_file)
371 #endif
372   hPutStrLn stderr (" done.")
373
374 -----------------------------------------------------------------------------
375 expandEnvVars :: PackageConfig -> [(String, String)] -> Bool -> IO PackageConfig
376 expandEnvVars pkg defines force = do
377    -- permit _all_ strings to contain ${..} environment variable references,
378    -- arguably too flexible.
379   nm       <- expandString (name pkg)
380   imp_dirs <- expandStrings (import_dirs pkg) 
381   src_dirs <- expandStrings (source_dirs pkg) 
382   lib_dirs <- expandStrings (library_dirs pkg) 
383   hs_libs  <- expandStrings (hs_libraries pkg)
384   ex_libs  <- expandStrings (extra_libraries pkg)
385   inc_dirs <- expandStrings (include_dirs pkg)
386   c_incs   <- expandStrings (c_includes pkg)
387   p_deps   <- expandStrings (package_deps pkg)
388   e_g_opts <- expandStrings (extra_ghc_opts pkg)
389   e_c_opts <- expandStrings (extra_cc_opts pkg)
390   e_l_opts <- expandStrings (extra_ld_opts pkg)
391   f_dirs   <- expandStrings (framework_dirs pkg)
392   e_frames <- expandStrings (extra_frameworks pkg)
393   return (pkg { name            = nm
394               , import_dirs     = imp_dirs
395               , source_dirs     = src_dirs
396               , library_dirs    = lib_dirs
397               , hs_libraries    = hs_libs
398               , extra_libraries = ex_libs
399               , include_dirs    = inc_dirs
400               , c_includes      = c_incs
401               , package_deps    = p_deps
402               , extra_ghc_opts  = e_g_opts
403               , extra_cc_opts   = e_c_opts
404               , extra_ld_opts   = e_l_opts
405               , framework_dirs  = f_dirs
406               , extra_frameworks= e_frames
407               })
408   where
409    expandStrings vs = do
410      xs <- mapM expandString vs
411        -- Flatten the elements of the expanded list; this is
412        -- to permit substitutions for list-valued variables. e.g.,
413        --     package_deps["${deps}"] where env var (say) 'deps'
414        -- is "base,haskell98,network"
415      return (concat (map (wordsBy (==',')) xs))
416    
417     -- Just for fun, keep this in the IO monad.
418    expandString :: String -> IO String
419    expandString str =
420      case break (=='$') str of
421        (xs, _:'{':rs) ->
422          case span (/='}') rs of
423            (nm,_:remainder) -> do
424               nm'  <- lookupEnvVar nm
425               str' <- expandString remainder
426               return (xs ++ nm' ++ str')
427            _ -> return str -- no closing '}'
428        _ -> return str     
429
430    lookupEnvVar nm = 
431      case lookup nm defines of
432        Just x | not (null x) -> return x
433        _      -> 
434         catch (System.getEnv nm)
435            (\ _ -> do dieOrForce force ("Unable to expand variable " ++ 
436                                         show nm)
437                       return "")
438
439 wordsBy :: (Char -> Bool) -> String -> [String]
440 wordsBy p s = case dropWhile p s of
441   "" -> []
442   s' -> w : wordsBy p s'' where (w,s'') = break p s'
443
444 -----------------------------------------------------------------------------
445
446 getProgramName :: IO String
447 getProgramName = liftM (`withoutSuffix` ".bin") getProgName
448    where str `withoutSuffix` suff
449             | suff `isSuffixOf` str = take (length str - length suff) str
450             | otherwise             = str
451
452 bye :: String -> IO a
453 bye s = putStr s >> exitWith ExitSuccess
454
455 die :: String -> IO a
456 die s = do { hFlush stdout ; hPutStr stderr s; exitWith (ExitFailure 1) }
457
458 dieOrForce :: Bool -> String -> IO ()
459 dieOrForce force s 
460   | force     = do hFlush stdout; hPutStrLn stderr (s ++ " (ignoring)")
461   | otherwise = die (s ++ "\n")
462
463 -----------------------------------------------------------------------------
464 -- Exceptions
465
466 #ifndef __GLASGOW_HASKELL__
467
468 eval_catch a h = a `seq` return ()
469 my_catch = IO.catch
470 my_throw = IO.fail
471
472 #else /* GHC */
473
474 my_throw = Exception.throw
475 #if __GLASGOW_HASKELL__ > 408
476 eval_catch = Exception.catch . Exception.evaluate
477 my_catch = Exception.catch
478 #else
479 eval_catch = Exception.catchAll
480 my_catch = Exception.catchAllIO
481 #endif
482
483 #endif
484
485 -----------------------------------------
486 --      Cut and pasted from ghc/compiler/SysTools
487
488 #if defined(mingw32_HOST_OS)
489 subst a b ls = map (\ x -> if x == a then b else x) ls
490 unDosifyPath xs = subst '\\' '/' xs
491
492 getExecDir :: String -> IO (Maybe String)
493 -- (getExecDir cmd) returns the directory in which the current
494 --                  executable, which should be called 'cmd', is running
495 -- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
496 -- you'll get "/a/b/c" back as the result
497 getExecDir cmd
498   = allocaArray len $ \buf -> do
499         ret <- getModuleFileName nullPtr buf len
500         if ret == 0 then return Nothing
501                     else do s <- peekCString buf
502                             return (Just (reverse (drop (length cmd) 
503                                                         (reverse (unDosifyPath s)))))
504   where
505     len = 2048::Int -- Plenty, PATH_MAX is 512 under Win32.
506
507 foreign import stdcall "GetModuleFileNameA" unsafe 
508   getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
509 #else
510 getExecDir :: String -> IO (Maybe String) 
511 getExecDir s = do return Nothing
512 #endif