[project @ 2004-12-03 13:01:28 by simonmar]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
1 {-# OPTIONS -fglasgow-exts #-}
2 -----------------------------------------------------------------------------
3 --
4 -- (c) The University of Glasgow 2004.
5 --
6 -- Package management tool
7 --
8 -----------------------------------------------------------------------------
9
10 -- TODO:
11 --      - validate modules
12 --      - expose/hide
13 --      - expanding of variables in new-style package conf
14 --      - version manipulation (checking whether old version exists,
15 --        hiding old version?)
16
17 module Main (main) where
18
19 import Version  ( version, targetOS, targetARCH )
20 import Distribution.InstalledPackageInfo
21 import Distribution.Compat.ReadP
22 import Distribution.ParseUtils  ( showError )
23 import Distribution.Package
24 import Distribution.Version
25 import Compat.Directory         ( getAppUserDataDirectory )
26 import Control.Exception        ( evaluate )
27 import qualified Control.Exception as Exception
28
29 import Prelude
30
31 #if __GLASGOW_HASKELL__ < 603
32 #include "config.h"
33 #endif
34
35 #if __GLASGOW_HASKELL__ >= 504
36 import System.Console.GetOpt
37 import Text.PrettyPrint
38 import qualified Control.Exception as Exception
39 #else
40 import GetOpt
41 import Pretty
42 import qualified Exception
43 #endif
44
45 import Data.Char        ( isSpace )
46 import Monad
47 import Directory
48 import System   ( getArgs, getProgName,
49                   system, exitWith,
50                   ExitCode(..)
51                 )
52 import System.IO
53 import Data.List ( isPrefixOf, isSuffixOf, intersperse )
54
55 #include "../../includes/ghcconfig.h"
56
57 #ifdef mingw32_HOST_OS
58 import Foreign
59
60 #if __GLASGOW_HASKELL__ >= 504
61 import Foreign.C.String
62 #else
63 import CString
64 #endif
65 #endif
66
67 -- -----------------------------------------------------------------------------
68 -- Entry point
69
70 main :: IO ()
71 main = do
72   args <- getArgs
73
74   case getOpt Permute flags args of
75         (cli,_,[]) | FlagHelp `elem` cli -> do
76            prog <- getProgramName
77            bye (usageInfo (usageHeader prog) flags)
78         (cli,_,[]) | FlagVersion `elem` cli ->
79            bye ourCopyright
80         (cli@(_:_),nonopts,[]) ->
81            runit cli nonopts
82         (_,_,errors) -> tryOldCmdLine errors args
83
84 -- If the new command-line syntax fails, then we try the old.  If that
85 -- fails too, then we output the original errors and the new syntax
86 -- (so the old syntax is still available, but hidden).
87 tryOldCmdLine :: [String] -> [String] -> IO ()
88 tryOldCmdLine errors args = do
89   case getOpt Permute oldFlags args of
90         (cli@(_:_),[],[]) -> 
91            oldRunit cli
92         _failed -> do
93            prog <- getProgramName
94            die (concat errors ++ usageInfo (usageHeader prog) flags)
95
96 -- -----------------------------------------------------------------------------
97 -- Command-line syntax
98
99 data Flag
100   = FlagUser
101   | FlagGlobal
102   | FlagHelp
103   | FlagVersion
104   | FlagConfig  FilePath
105   | FlagGlobalConfig FilePath
106   | FlagForce
107   | FlagAutoGHCiLibs
108   deriving Eq
109
110 flags :: [OptDescr Flag]
111 flags = [
112   Option [] ["user"] (NoArg FlagUser)
113         "use the current user's package database",
114   Option [] ["global"] (NoArg FlagGlobal)
115         "(default) use the global package database",
116   Option ['f'] ["package-conf"] (ReqArg FlagConfig "FILE")
117         "act upon specified package config file (only)",
118   Option [] ["global-conf"] (ReqArg FlagGlobalConfig "FILE")
119         "location of the global package config",
120   Option [] ["force"] (NoArg FlagForce)
121         "ignore missing dependencies, directories, and libraries",
122   Option ['g'] ["auto-ghci-libs"] (NoArg FlagAutoGHCiLibs)
123         "automatically build libs for GHCi (with register)",
124   Option ['?'] ["help"] (NoArg FlagHelp)
125         "display this help and exit",
126    Option ['V'] ["version"] (NoArg FlagVersion)
127         "output version information and exit"
128   ]
129
130 ourCopyright :: String
131 ourCopyright = "GHC package manager version " ++ version ++ "\n"
132
133 usageHeader :: String -> String
134 usageHeader prog = substProg prog $
135   "Usage:\n" ++
136   "  $p {--help | -?}\n" ++
137   "    Produce this usage message.\n" ++
138   "\n" ++
139   "  $p register {filename | -} [--user | --global]\n" ++
140   "    Register the package using the specified installed package\n" ++
141   "    description. The syntax for the latter is given in the $p\n" ++
142   "    documentation.\n" ++
143   "\n" ++
144   "  $p unregister {pkg-id}\n" ++
145   "    Unregister the specified package.\n" ++
146   "\n" ++
147   "  $p expose {pkg-id}\n" ++
148   "    Expose the specified package.\n" ++
149   "\n" ++
150   "  $p hide {pkg-id}\n" ++
151   "    Hide the specified package.\n" ++
152   "\n" ++
153   "  $p list [--global | --user]\n" ++
154   "    List all registered packages, both global and user (unless either\n" ++
155   "    --global or --user is specified), and both hidden and exposed.\n" ++
156   "\n" ++
157   "  $p describe {pkg-id}\n" ++
158   "    Give the registered description for the specified package. The\n" ++
159   "    description is returned in precisely the syntax required by $p\n" ++
160   "    register.\n" ++
161   "\n" ++
162   "  $p field {pkg-id} {field}\n" ++
163   "    Extract the specified field of the package description for the\n" ++
164   "    specified package.\n"
165
166 substProg :: String -> String -> String
167 substProg _ [] = []
168 substProg prog ('$':'p':xs) = prog ++ substProg prog xs
169 substProg prog (c:xs) = c : substProg prog xs
170
171 -- -----------------------------------------------------------------------------
172 -- Do the business
173
174 runit :: [Flag] -> [String] -> IO ()
175 runit cli nonopts = do
176   prog <- getProgramName
177   dbs <- getPkgDatabases cli
178   db_stack <- mapM readParseDatabase dbs
179   let
180         force = FlagForce `elem` cli
181         auto_ghci_libs = FlagAutoGHCiLibs `elem` cli
182   --
183   -- first, parse the command
184   case nonopts of
185     ["register", filename] -> 
186         registerPackage filename [] db_stack auto_ghci_libs False force
187     ["update", filename] -> 
188         registerPackage filename [] db_stack auto_ghci_libs True force
189     ["unregister", pkgid_str] -> do
190         pkgid <- readPkgId pkgid_str
191         unregisterPackage db_stack pkgid
192     ["expose", pkgid_str] -> do
193         pkgid <- readPkgId pkgid_str
194         exposePackage pkgid db_stack
195     ["hide",   pkgid_str] -> do
196         pkgid <- readPkgId pkgid_str
197         hidePackage pkgid db_stack
198     ["list"] -> do
199         listPackages db_stack
200     ["describe", pkgid_str] -> do
201         pkgid <- readPkgId pkgid_str
202         describePackage db_stack pkgid
203     ["field", pkgid_str, field] -> do
204         pkgid <- readPkgId pkgid_str
205         describeField db_stack pkgid field
206     [] -> do
207         die ("missing command\n" ++ 
208                 usageInfo (usageHeader prog) flags)
209     (_cmd:_) -> do
210         die ("command-line syntax error\n" ++ 
211                 usageInfo (usageHeader prog) flags)
212
213 parseCheck :: ReadP a a -> String -> String -> IO a
214 parseCheck parser str what = 
215   case readP_to_S parser str of
216     [(x,ys)] | all isSpace ys -> return x
217     _ -> die ("cannot parse \'" ++ str ++ "\' as a " ++ what)
218
219 readPkgId :: String -> IO PackageIdentifier
220 readPkgId str = parseCheck parsePackageId str "package identifier"
221
222 -- -----------------------------------------------------------------------------
223 -- Package databases
224
225 -- Some commands operate on a single database:
226 --      register, unregister, expose, hide
227 -- however these commands also check the union of the available databases
228 -- in order to check consistency.  For example, register will check that
229 -- dependencies exist before registering a package.
230 --
231 -- Some commands operate  on multiple databases, with overlapping semantics:
232 --      list, describe, field
233
234 type PackageDBName  = FilePath
235 type PackageDB      = [InstalledPackageInfo]
236
237 type PackageDBStack = [(PackageDBName,PackageDB)]
238         -- A stack of package databases.  Convention: head is the topmost
239         -- in the stack.  Earlier entries override later one.
240
241 -- The output of this function is the list of databases to act upon, with
242 -- the "topmost" overlapped database last.  The commands which operate on a
243 -- single database will use the last one.  Commands which operate on multiple
244 -- databases will interpret the databases as overlapping.
245 getPkgDatabases :: [Flag] -> IO [PackageDBName]
246 getPkgDatabases flags = do
247   -- first we determine the location of the global package config.  On Windows,
248   -- this is found relative to the ghc-pkg.exe binary, whereas on Unix the
249   -- location is passed to the binary using the --global-config flag by the
250   -- wrapper script.
251   let err_msg = "missing --global-conf option, location of global package.conf unknown\n"
252   global_conf <- 
253      case [ f | FlagGlobalConfig f <- flags ] of
254         [] -> do mb_dir <- getExecDir "/bin/ghc-pkg.exe"
255                  case mb_dir of
256                         Nothing  -> die err_msg
257                         Just dir -> return (dir `joinFileName` "package.conf")
258         fs -> return (last fs)
259
260   -- get the location of the user package database, and create it if necessary
261   appdir <- getAppUserDataDirectory "ghc"
262
263   let
264         subdir = targetARCH ++ '-':targetOS ++ '-':version
265         user_conf = appdir `joinFileName` subdir `joinFileName` "package.conf"
266   b <- doesFileExist user_conf
267   when (not b) $ do
268         putStrLn ("Creating user package database in " ++ user_conf)
269         createParents user_conf
270         writeFile user_conf emptyPackageConfig
271
272   let
273         databases = foldl addDB [global_conf] flags
274
275         -- implement the following rules:
276         --      global database is the default
277         --      --user means overlap with the user database
278         --      --global means reset to just the global database
279         --      -f <file> means overlap with <file>
280         addDB dbs FlagUser       = user_conf : dbs
281         addDB dbs FlagGlobal     = [global_conf]
282         addDB dbs (FlagConfig f) = f : dbs
283         addDB dbs _              = dbs
284
285   return databases
286
287 readParseDatabase :: PackageDBName -> IO (PackageDBName,PackageDB)
288 readParseDatabase filename = do
289   str <- readFile filename
290   let packages = read str
291   evaluate packages
292     `Exception.catch` \_ -> 
293         die (filename ++ ": parse error in package config file")
294   return (filename,packages)
295
296 emptyPackageConfig :: String
297 emptyPackageConfig = "[]"
298
299 -- -----------------------------------------------------------------------------
300 -- Registering
301
302 registerPackage :: FilePath
303                 -> [(String,String)] --  defines, ToDo: maybe remove?
304                 -> PackageDBStack
305                 -> Bool         -- auto_ghci_libs
306                 -> Bool         -- update
307                 -> Bool         -- force
308                 -> IO ()
309 registerPackage input defines db_stack auto_ghci_libs update force = do
310   let
311         db_to_operate_on = head db_stack
312         db_filename      = fst db_to_operate_on
313   --
314   checkConfigAccess db_filename
315
316   s <-
317     case input of
318       "-" -> do
319         putStr "Reading package info from stdin... "
320         getContents
321       f   -> do
322         putStr ("Reading package info from " ++ show f ++ " ")
323         readFile f
324
325   pkg <- parsePackageInfo s defines force
326   putStrLn "done."
327
328   validatePackageConfig pkg db_stack auto_ghci_libs update force
329   new_details <- updatePackageDB db_stack (snd db_to_operate_on) pkg
330   savePackageConfig db_filename
331   maybeRestoreOldConfig db_filename $
332     writeNewConfig db_filename new_details
333
334 parsePackageInfo
335         :: String
336         -> [(String,String)]
337         -> Bool
338         -> IO InstalledPackageInfo
339 parsePackageInfo str defines force =
340   case parseInstalledPackageInfo str of
341     Right ok -> return ok
342     Left err -> die (showError err)
343
344 -- Used for converting versionless package names to new
345 -- PackageIdentifiers.  "Version [] []" is special: it means "no
346 -- version" or "any version"
347 pkgNameToId :: String -> PackageIdentifier
348 pkgNameToId name = PackageIdentifier name (Version [] [])
349
350 -- -----------------------------------------------------------------------------
351 -- Unregistering
352
353 unregisterPackage :: PackageDBStack -> PackageIdentifier -> IO ()
354 unregisterPackage [] _ = error "unregisterPackage"
355 unregisterPackage ((db_name, pkgs) : _) pkgid = do  
356   checkConfigAccess db_name
357   p <- findPackage [(db_name,pkgs)] pkgid
358   let pid = package p
359   savePackageConfig db_name
360   maybeRestoreOldConfig db_name $
361     writeNewConfig db_name (filter ((/= pid) . package) pkgs)
362
363 -- -----------------------------------------------------------------------------
364 -- Exposing
365
366 exposePackage :: PackageIdentifier ->  PackageDBStack -> IO ()
367 exposePackage = error "TODO"
368
369 -- -----------------------------------------------------------------------------
370 -- Hiding
371
372 hidePackage :: PackageIdentifier ->  PackageDBStack -> IO ()
373 hidePackage = error "TODO"
374
375 -- -----------------------------------------------------------------------------
376 -- Listing packages
377
378 listPackages ::  PackageDBStack -> IO ()
379 listPackages db_confs = do
380   mapM_ show_pkgconf (reverse db_confs)
381   where show_pkgconf (db_name,pkg_confs) =
382           hPutStrLn stdout (render $
383                 text (db_name ++ ":") $$ nest 4 packages
384                 )
385            where packages = fsep (punctuate comma (map pp_pkg pkg_confs))
386                  pp_pkg = text . showPackageId . package
387
388
389 -- -----------------------------------------------------------------------------
390 -- Describe
391
392 describePackage :: PackageDBStack -> PackageIdentifier -> IO ()
393 describePackage db_stack pkgid = do
394   p <- findPackage db_stack pkgid
395   putStrLn (showInstalledPackageInfo p)
396
397 findPackage :: PackageDBStack -> PackageIdentifier -> IO InstalledPackageInfo
398 findPackage db_stack pkgid
399   = case [ p | p <- all_pkgs, pkgid `matches` p ] of
400         []  -> die ("cannot find package " ++ showPackageId pkgid)
401         [p] -> return p
402         ps  -> die ("package " ++ showPackageId pkgid ++ 
403                         " matches multiple packages: " ++ 
404                         concat (intersperse ", " (
405                                  map (showPackageId.package) ps)))
406   where
407         all_pkgs = concat (map snd db_stack)
408
409 matches :: PackageIdentifier -> InstalledPackageInfo -> Bool
410 pid `matches` p = 
411  pid == package p || 
412  not (realVersion pid) && pkgName pid == pkgName (package p)
413
414 -- -----------------------------------------------------------------------------
415 -- Field
416
417 describeField :: PackageDBStack -> PackageIdentifier -> String -> IO ()
418 describeField db_stack pkgid field = do
419   case toField field of
420     Nothing -> die ("unknown field: " ++ field)
421     Just fn -> do
422         p <- findPackage db_stack pkgid 
423         putStrLn (fn p)
424
425 toField :: String -> Maybe (InstalledPackageInfo -> String)
426 -- backwards compatibility:
427 toField "import_dirs"     = Just $ strList . importDirs
428 toField "source_dirs"     = Just $ strList . importDirs
429 toField "library_dirs"    = Just $ strList . libraryDirs
430 toField "hs_libraries"    = Just $ strList . hsLibraries
431 toField "extra_libraries" = Just $ strList . extraLibraries
432 toField "include_dirs"    = Just $ strList . includeDirs
433 toField "c_includes"      = Just $ strList . includes
434 toField "package_deps"    = Just $ strList . map showPackageId. depends
435 toField "extra_cc_opts"   = Just $ strList . extraCcOpts
436 toField "extra_ld_opts"   = Just $ strList . extraLdOpts  
437 toField "framework_dirs"  = Just $ strList . frameworkDirs  
438 toField "extra_frameworks"= Just $ strList . extraFrameworks  
439 toField s                 = showInstalledPackageInfoField s
440
441 strList :: [String] -> String
442 strList = show
443
444 -- -----------------------------------------------------------------------------
445 -- Manipulating package.conf files
446
447 checkConfigAccess :: FilePath -> IO ()
448 checkConfigAccess filename = do
449   access <- getPermissions filename
450   when (not (writable access))
451       (die (filename ++ ": you don't have permission to modify this file"))
452
453 maybeRestoreOldConfig :: FilePath -> IO () -> IO ()
454 maybeRestoreOldConfig filename io
455   = io `catch` \e -> do
456         hPutStrLn stderr (show e)
457         hPutStr stdout ("\nWARNING: an error was encountered while the new \n"++
458                           "configuration was being written.  Attempting to \n"++
459                           "restore the old configuration... ")
460         renameFile (filename ++ ".old")  filename
461         hPutStrLn stdout "done."
462         ioError e
463
464 writeNewConfig :: FilePath -> [InstalledPackageInfo] -> IO ()
465 writeNewConfig filename packages = do
466   hPutStr stdout "Writing new package config file... "
467   h <- openFile filename WriteMode
468   hPutStrLn h (show packages)
469   hClose h
470   hPutStrLn stdout "done."
471
472 savePackageConfig :: FilePath -> IO ()
473 savePackageConfig filename = do
474   hPutStr stdout "Saving old package config file... "
475     -- mv rather than cp because we've already done an hGetContents
476     -- on this file so we won't be able to open it for writing
477     -- unless we move the old one out of the way...
478   let oldFile = filename ++ ".old"
479   doesExist <- doesFileExist oldFile  `catch` (\ _ -> return False)
480   when doesExist (removeFile oldFile `catch` (const $ return ()))
481   catch (renameFile filename oldFile)
482         (\ err -> do
483                 hPutStrLn stderr (unwords [ "Unable to rename "
484                                           , show filename
485                                           , " to "
486                                           , show oldFile
487                                           ])
488                 ioError err)
489   hPutStrLn stdout "done."
490
491 -----------------------------------------------------------------------------
492 -- Sanity-check a new package config, and automatically build GHCi libs
493 -- if requested.
494
495 validatePackageConfig :: InstalledPackageInfo
496                       -> PackageDBStack
497                       -> Bool   -- auto-ghc-libs
498                       -> Bool   -- update
499                       -> Bool   -- force
500                       -> IO ()
501 validatePackageConfig pkg db_stack auto_ghci_libs update force = do
502   checkDuplicates db_stack pkg update
503   mapM_ (checkDep db_stack force) (depends pkg)
504   mapM_ (checkDir force) (importDirs pkg)
505   mapM_ (checkDir force) (libraryDirs pkg)
506   mapM_ (checkDir force) (includeDirs pkg)
507   mapM_ (checkHSLib (libraryDirs pkg) auto_ghci_libs force) (hsLibraries pkg)
508   -- ToDo: check these somehow?
509   --    extra_libraries :: [String],
510   --    c_includes      :: [String],
511
512
513 checkDuplicates :: PackageDBStack -> InstalledPackageInfo -> Bool -> IO ()
514 checkDuplicates db_stack pkg update = do
515   let
516         pkgid = package pkg
517
518         (_top_db_name, pkgs) : _  = db_stack
519
520         pkgs_with_same_name = 
521                 [ p | p <- pkgs, pkgName (package p) == pkgName pkgid]
522         exposed_pkgs_with_same_name =
523                 filter exposed pkgs_with_same_name
524   --
525   -- Check whether this package id already exists in this DB
526   --
527   when (not update && (package pkg `elem` map package pkgs)) $
528        die ("package " ++ showPackageId pkgid ++ " is already installed")
529   --
530   -- if we are exposing this new package, then check that
531   -- there are no other exposed packages with the same name.
532   --
533   when (not update && exposed pkg && not (null exposed_pkgs_with_same_name)) $
534         die ("trying to register " ++ showPackageId pkgid 
535                   ++ " as exposed, but "
536                   ++ showPackageId (package (head exposed_pkgs_with_same_name))
537                   ++ " is also exposed.")
538
539
540 checkDir :: Bool -> String -> IO ()
541 checkDir force d
542  | "$libdir" `isPrefixOf` d = return ()
543         -- can't check this, because we don't know what $libdir is
544  | otherwise = do
545    there <- doesDirectoryExist d
546    when (not there)
547        (dieOrForce force (d ++ " doesn't exist or isn't a directory"))
548
549 checkDep :: PackageDBStack -> Bool -> PackageIdentifier -> IO ()
550 checkDep db_stack force pkgid
551   | real_version && pkgid `elem` pkgids = return ()
552   | not real_version && pkgName pkgid `elem` pkg_names = return ()
553   | otherwise = dieOrForce force ("dependency " ++ showPackageId pkgid
554                                         ++ " doesn't exist")
555   where
556         -- for backwards compat, we treat 0.0 as a special version,
557         -- and don't check that it actually exists.
558         real_version = realVersion pkgid
559         
560         all_pkgs = concat (map snd db_stack)
561         pkgids = map package all_pkgs
562         pkg_names = map pkgName pkgids
563
564 realVersion :: PackageIdentifier -> Bool
565 realVersion pkgid = versionBranch (pkgVersion pkgid) /= []
566
567 checkHSLib :: [String] -> Bool -> Bool -> String -> IO ()
568 checkHSLib dirs auto_ghci_libs force lib = do
569   let batch_lib_file = "lib" ++ lib ++ ".a"
570   bs <- mapM (doesLibExistIn batch_lib_file) dirs
571   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
572         [] -> dieOrForce force ("cannot find `" ++ batch_lib_file ++
573                                  "' on library path") 
574         (dir:_) -> checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
575
576 doesLibExistIn :: String -> String -> IO Bool
577 doesLibExistIn lib d
578  | "$libdir" `isPrefixOf` d = return True
579  | otherwise                = doesFileExist (d ++ '/':lib)
580
581 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
582 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build
583   | auto_build = autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
584   | otherwise  = do
585       bs <- mapM (doesLibExistIn ghci_lib_file) dirs
586       case [dir | (exists,dir) <- zip bs dirs, exists] of
587         []    -> hPutStrLn stderr ("warning: can't find GHCi lib `" ++ ghci_lib_file ++ "'")
588         (_:_) -> return ()
589   where
590     ghci_lib_file = lib ++ ".o"
591
592 -- automatically build the GHCi version of a batch lib, 
593 -- using ld --whole-archive.
594
595 autoBuildGHCiLib :: String -> String -> String -> IO ()
596 autoBuildGHCiLib dir batch_file ghci_file = do
597   let ghci_lib_file  = dir ++ '/':ghci_file
598       batch_lib_file = dir ++ '/':batch_file
599   hPutStr stderr ("building GHCi library `" ++ ghci_lib_file ++ "'...")
600 #if defined(darwin_TARGET_OS)
601   r <- system("ld -r -x -o " ++ ghci_lib_file ++ 
602                  " -all_load " ++ batch_lib_file)
603 #elif defined(mingw32_HOST_OS)
604   execDir <- getExecDir "/bin/ghc-pkg.exe"
605   r <- system (maybe "" (++"/gcc-lib/") execDir++"ld -r -x -o " ++ 
606                 ghci_lib_file ++ " --whole-archive " ++ batch_lib_file)
607 #else
608   r <- system("ld -r -x -o " ++ ghci_lib_file ++ 
609                  " --whole-archive " ++ batch_lib_file)
610 #endif
611   when (r /= ExitSuccess) $ exitWith r
612   hPutStrLn stderr (" done.")
613
614 -- -----------------------------------------------------------------------------
615 -- Updating the DB with the new package.
616
617 updatePackageDB
618         :: PackageDBStack
619         -> [InstalledPackageInfo]
620         -> InstalledPackageInfo
621         -> IO [InstalledPackageInfo]
622 updatePackageDB db_stack pkgs new_pkg = do
623   let
624         -- we update dependencies without version numbers to
625         -- match the actual versions of the relevant packages instaled.
626         updateDeps p = p{depends = map resolveDep (depends p)}
627
628         resolveDep pkgid
629            | realVersion pkgid  = pkgid
630            | otherwise          = lookupDep (pkgName pkgid)
631         
632         lookupDep name
633            = head [ pid | p <- concat (map snd db_stack), 
634                           let pid = package p,
635                           pkgName pid == name ]
636
637         is_exposed = exposed new_pkg
638         pkgid      = package new_pkg
639         name       = pkgName pkgid
640
641         pkgs' = [ maybe_hide p | p <- pkgs, package p /= pkgid ]
642         
643         -- When update is on, and we're exposing the new package,
644         -- we hide any packages with the same name (different versions)
645         -- in the current DB.  Earlier checks will have failed if
646         -- update isn't on.
647         maybe_hide p
648           | is_exposed && pkgName (package p) == name = p{ exposed = False }
649           | otherwise = p
650   --
651   return (pkgs'++[updateDeps new_pkg])
652
653 -- -----------------------------------------------------------------------------
654 -- Searching for modules
655
656 #if not_yet
657
658 findModules :: [FilePath] -> IO [String]
659 findModules paths = 
660   mms <- mapM searchDir paths
661   return (concat mms)
662
663 searchDir path prefix = do
664   fs <- getDirectoryEntries path `catch` \_ -> return []
665   searchEntries path prefix fs
666
667 searchEntries path prefix [] = return []
668 searchEntries path prefix (f:fs)
669   | looks_like_a_module  =  do
670         ms <- searchEntries path prefix fs
671         return (prefix `joinModule` f : ms)
672   | looks_like_a_component  =  do
673         ms <- searchDir (path `joinFilename` f) (prefix `joinModule` f)
674         ms' <- searchEntries path prefix fs
675         return (ms ++ ms')      
676   | otherwise
677         searchEntries path prefix fs
678
679   where
680         (base,suffix) = splitFileExt f
681         looks_like_a_module = 
682                 suffix `elem` haskell_suffixes && 
683                 all okInModuleName base
684         looks_like_a_component =
685                 null suffix && all okInModuleName base
686
687 okInModuleName c
688
689 #endif
690
691 -- -----------------------------------------------------------------------------
692 -- The old command-line syntax, supported for backwards compatibility
693
694 data OldFlag 
695   = OF_Config FilePath
696   | OF_Input FilePath
697   | OF_List
698   | OF_ListLocal
699   | OF_Add Bool {- True => replace existing info -}
700   | OF_Remove String | OF_Show String 
701   | OF_Field String | OF_AutoGHCiLibs | OF_Force
702   | OF_DefinedName String String
703   | OF_GlobalConfig FilePath
704   deriving (Eq)
705
706 isAction :: OldFlag -> Bool
707 isAction OF_Config{}        = False
708 isAction OF_Field{}         = False
709 isAction OF_Input{}         = False
710 isAction OF_AutoGHCiLibs{}  = False
711 isAction OF_Force{}         = False
712 isAction OF_DefinedName{}   = False
713 isAction OF_GlobalConfig{}  = False
714 isAction _                  = True
715
716 oldFlags :: [OptDescr OldFlag]
717 oldFlags = [
718   Option ['f'] ["config-file"] (ReqArg OF_Config "FILE")
719         "use the specified package config file",
720   Option ['l'] ["list-packages"] (NoArg OF_List)
721         "list packages in all config files",
722   Option ['L'] ["list-local-packages"] (NoArg OF_ListLocal)
723         "list packages in the specified config file",
724   Option ['a'] ["add-package"] (NoArg (OF_Add False))
725         "add a new package",
726   Option ['u'] ["update-package"] (NoArg (OF_Add True))
727         "update package with new configuration",
728   Option ['i'] ["input-file"] (ReqArg OF_Input "FILE")
729         "read new package info from specified file",
730   Option ['s'] ["show-package"] (ReqArg OF_Show "NAME")
731         "show the configuration for package NAME",
732   Option [] ["field"] (ReqArg OF_Field "FIELD")
733         "(with --show-package) Show field FIELD only",
734   Option [] ["force"] (NoArg OF_Force)
735         "ignore missing directories/libraries",
736   Option ['r'] ["remove-package"] (ReqArg OF_Remove "NAME")
737         "remove an installed package",
738   Option ['g'] ["auto-ghci-libs"] (NoArg OF_AutoGHCiLibs)
739         "automatically build libs for GHCi (with -a)",
740   Option ['D'] ["define-name"] (ReqArg toDefined "NAME=VALUE")
741         "define NAME as VALUE",
742   Option [] ["global-conf"] (ReqArg OF_GlobalConfig "FILE")
743         "location of the global package config"
744   ]
745  where
746   toDefined str = 
747     case break (=='=') str of
748       (nm,[]) -> OF_DefinedName nm []
749       (nm,_:val) -> OF_DefinedName nm val
750
751 oldRunit :: [OldFlag] -> IO ()
752 oldRunit clis = do
753   let config_flags = [ f | Just f <- map conv clis ]
754
755       conv (OF_GlobalConfig f) = Just (FlagGlobalConfig f)
756       conv (OF_Config f)       = Just (FlagConfig f)
757       conv _                   = Nothing
758
759   db_names <- getPkgDatabases config_flags
760   db_stack <- mapM readParseDatabase db_names
761
762   let fields = [ f | OF_Field f <- clis ]
763
764   let auto_ghci_libs = any isAuto clis 
765          where isAuto OF_AutoGHCiLibs = True; isAuto _ = False
766       input_file = head ([ f | (OF_Input f) <- clis] ++ ["-"])
767
768       force = OF_Force `elem` clis
769       
770       defines = [ (nm,val) | OF_DefinedName nm val <- clis ]
771
772   case [ c | c <- clis, isAction c ] of
773     [ OF_List ]      -> listPackages db_stack
774     [ OF_ListLocal ] -> listPackages db_stack
775     [ OF_Add upd ]   -> registerPackage input_file defines db_stack
776                                 auto_ghci_libs upd force
777     [ OF_Remove p ]  -> unregisterPackage db_stack (pkgNameToId p)
778     [ OF_Show p ]
779         | null fields -> describePackage db_stack (pkgNameToId p)
780         | otherwise   -> mapM_ (describeField db_stack (pkgNameToId p)) fields
781     _            -> do prog <- getProgramName
782                        die (usageInfo (usageHeader prog) flags)
783
784 -- ---------------------------------------------------------------------------
785
786 #ifdef OLD_STUFF
787 -- ToDo: reinstate
788 expandEnvVars :: PackageConfig -> [(String, String)]
789         -> Bool -> IO PackageConfig
790 expandEnvVars pkg defines force = do
791    -- permit _all_ strings to contain ${..} environment variable references,
792    -- arguably too flexible.
793   nm       <- expandString  (name pkg)
794   imp_dirs <- expandStrings (import_dirs pkg) 
795   src_dirs <- expandStrings (source_dirs pkg) 
796   lib_dirs <- expandStrings (library_dirs pkg) 
797   hs_libs  <- expandStrings (hs_libraries pkg)
798   ex_libs  <- expandStrings (extra_libraries pkg)
799   inc_dirs <- expandStrings (include_dirs pkg)
800   c_incs   <- expandStrings (c_includes pkg)
801   p_deps   <- expandStrings (package_deps pkg)
802   e_g_opts <- expandStrings (extra_ghc_opts pkg)
803   e_c_opts <- expandStrings (extra_cc_opts pkg)
804   e_l_opts <- expandStrings (extra_ld_opts pkg)
805   f_dirs   <- expandStrings (framework_dirs pkg)
806   e_frames <- expandStrings (extra_frameworks pkg)
807   return (pkg { name            = nm
808               , import_dirs     = imp_dirs
809               , source_dirs     = src_dirs
810               , library_dirs    = lib_dirs
811               , hs_libraries    = hs_libs
812               , extra_libraries = ex_libs
813               , include_dirs    = inc_dirs
814               , c_includes      = c_incs
815               , package_deps    = p_deps
816               , extra_ghc_opts  = e_g_opts
817               , extra_cc_opts   = e_c_opts
818               , extra_ld_opts   = e_l_opts
819               , framework_dirs  = f_dirs
820               , extra_frameworks= e_frames
821               })
822   where
823    expandStrings :: [String] -> IO [String]
824    expandStrings = liftM concat . mapM expandSpecial
825
826    -- Permit substitutions for list-valued variables (but only when
827    -- they occur alone), e.g., package_deps["${deps}"] where env var
828    -- (say) 'deps' is "base,haskell98,network"
829    expandSpecial :: String -> IO [String]
830    expandSpecial str =
831       let expand f = liftM f $ expandString str
832       in case splitString str of
833          [Var _] -> expand (wordsBy (== ','))
834          _ -> expand (\x -> [x])
835
836    expandString :: String -> IO String
837    expandString = liftM concat . mapM expandElem . splitString
838
839    expandElem :: Elem -> IO String
840    expandElem (String s) = return s
841    expandElem (Var v)    = lookupEnvVar v
842
843    lookupEnvVar :: String -> IO String
844    lookupEnvVar nm = 
845      case lookup nm defines of
846        Just x | not (null x) -> return x
847        _      -> 
848         catch (System.getEnv nm)
849            (\ _ -> do dieOrForce force ("Unable to expand variable " ++ 
850                                         show nm)
851                       return "")
852
853 data Elem = String String | Var String
854
855 splitString :: String -> [Elem]
856 splitString "" = []
857 splitString str =
858    case break (== '$') str of
859       (pre, _:'{':xs) ->
860          case span (/= '}') xs of
861             (var, _:suf) ->
862                (if null pre then id else (String pre :)) (Var var : splitString suf)
863             _ -> [String str]   -- no closing brace
864       _ -> [String str]   -- no dollar/opening brace combo
865
866 -- wordsBy isSpace == words
867 wordsBy :: (Char -> Bool) -> String -> [String]
868 wordsBy p s = case dropWhile p s of
869   "" -> []
870   s' -> w : wordsBy p s'' where (w,s'') = break p s'
871 #endif
872
873 -----------------------------------------------------------------------------
874
875 getProgramName :: IO String
876 getProgramName = liftM (`withoutSuffix` ".bin") getProgName
877    where str `withoutSuffix` suff
878             | suff `isSuffixOf` str = take (length str - length suff) str
879             | otherwise             = str
880
881 bye :: String -> IO a
882 bye s = putStr s >> exitWith ExitSuccess
883
884 die :: String -> IO a
885 die s = do 
886   hFlush stdout
887   prog <- getProgramName
888   hPutStrLn stderr (prog ++ ": " ++ s)
889   exitWith (ExitFailure 1)
890
891 dieOrForce :: Bool -> String -> IO ()
892 dieOrForce force s 
893   | force     = do hFlush stdout; hPutStrLn stderr (s ++ " (ignoring)")
894   | otherwise = die s
895
896
897 -----------------------------------------------------------------------------
898 -- Create a hierarchy of directories
899
900 createParents :: FilePath -> IO ()
901 createParents dir = do
902   let parent = directoryOf dir
903   b <- doesDirectoryExist parent
904   when (not b) $ do
905         createParents parent
906         createDirectory parent
907
908 -----------------------------------------
909 --      Cut and pasted from ghc/compiler/SysTools
910
911 #if defined(mingw32_HOST_OS)
912 subst a b ls = map (\ x -> if x == a then b else x) ls
913 unDosifyPath xs = subst '\\' '/' xs
914
915 getExecDir :: String -> IO (Maybe String)
916 -- (getExecDir cmd) returns the directory in which the current
917 --                  executable, which should be called 'cmd', is running
918 -- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
919 -- you'll get "/a/b/c" back as the result
920 getExecDir cmd
921   = allocaArray len $ \buf -> do
922         ret <- getModuleFileName nullPtr buf len
923         if ret == 0 then return Nothing
924                     else do s <- peekCString buf
925                             return (Just (reverse (drop (length cmd) 
926                                                         (reverse (unDosifyPath s)))))
927   where
928     len = 2048::Int -- Plenty, PATH_MAX is 512 under Win32.
929
930 foreign import stdcall unsafe  "GetModuleFileNameA"
931   getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
932 #else
933 getExecDir :: String -> IO (Maybe String) 
934 getExecDir _ = return Nothing
935 #endif
936
937 -- -----------------------------------------------------------------------------
938 -- Utils from Krasimir's FilePath library, copied here for now
939
940 directoryOf :: FilePath -> FilePath
941 directoryOf = fst.splitFileName
942
943 splitFileName :: FilePath -> (String, String)
944 splitFileName p = (reverse (path2++drive), reverse fname)
945   where
946 #ifdef mingw32_TARGET_OS
947     (path,drive) = break (== ':') (reverse p)
948 #else
949     (path,drive) = (reverse p,"")
950 #endif
951     (fname,path1) = break isPathSeparator path
952     path2 = case path1 of
953       []                           -> "."
954       [_]                          -> path1   -- don't remove the trailing slash if 
955                                               -- there is only one character
956       (c:path) | isPathSeparator c -> path
957       _                            -> path1
958
959 joinFileName :: String -> String -> FilePath
960 joinFileName ""  fname = fname
961 joinFileName "." fname = fname
962 joinFileName dir fname
963   | isPathSeparator (last dir) = dir++fname
964   | otherwise                  = dir++pathSeparator:fname
965
966 isPathSeparator :: Char -> Bool
967 isPathSeparator ch =
968 #ifdef mingw32_TARGET_OS
969   ch == '/' || ch == '\\'
970 #else
971   ch == '/'
972 #endif
973
974 pathSeparator :: Char
975 #ifdef mingw32_TARGET_OS
976 pathSeparator = '\\'
977 #else
978 pathSeparator = '/'
979 #endif