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