follow change in System.Posix.Internals.c_open
[ghc-hetmet.git] / utils / ghc-pkg / Main.hs
1 {-# OPTIONS -fglasgow-exts -cpp #-}
2 -----------------------------------------------------------------------------
3 --
4 -- (c) The University of Glasgow 2004.
5 --
6 -- Package management tool
7 --
8 -----------------------------------------------------------------------------
9
10 -- TODO:
11 -- * validate modules
12 -- * expanding of variables in new-style package conf
13 -- * version manipulation (checking whether old version exists,
14 --   hiding old version?)
15
16 module Main (main) where
17
18 import Version ( version, targetOS, targetARCH )
19 import Distribution.ModuleName hiding (main)
20 import Distribution.InstalledPackageInfo hiding (depends)
21 import Distribution.Compat.ReadP
22 import Distribution.ParseUtils
23 import Distribution.Package
24 import Distribution.Text
25 import Distribution.Version
26 import System.FilePath
27 import System.Cmd       ( rawSystem )
28 import System.Directory ( getAppUserDataDirectory, createDirectoryIfMissing )
29
30 import Prelude
31
32 #include "../../includes/ghcconfig.h"
33
34 import System.Console.GetOpt
35 import Text.PrettyPrint
36 #if __GLASGOW_HASKELL__ >= 609
37 import qualified Control.Exception as Exception
38 #else
39 import qualified Control.Exception.Extensible as Exception
40 #endif
41 import Data.Maybe
42
43 import Data.Char ( isSpace, toLower )
44 import Control.Monad
45 import System.Directory ( doesDirectoryExist, getDirectoryContents,
46                           doesFileExist, renameFile, removeFile )
47 import System.Exit ( exitWith, ExitCode(..) )
48 import System.Environment ( getArgs, getProgName, getEnv )
49 import System.IO
50 import System.IO.Error (try)
51 import Data.List
52 import Control.Concurrent
53
54 import Foreign
55 import Foreign.C
56 #ifdef mingw32_HOST_OS
57 import GHC.ConsoleHandler
58 #else
59 import System.Posix hiding (fdToHandle)
60 #endif
61
62 import IO ( isPermissionError )
63 import System.Posix.Internals
64 #if __GLASGOW_HASKELL__ >= 611
65 import GHC.IO.Handle.FD (fdToHandle)
66 #else
67 import GHC.Handle (fdToHandle)
68 #endif
69
70 #if defined(GLOB)
71 import System.Process(runInteractiveCommand)
72 import qualified System.Info(os)
73 #endif
74
75 -- -----------------------------------------------------------------------------
76 -- Entry point
77
78 main :: IO ()
79 main = do
80   args <- getArgs
81
82   case getOpt Permute (flags ++ deprecFlags) args of
83         (cli,_,[]) | FlagHelp `elem` cli -> do
84            prog <- getProgramName
85            bye (usageInfo (usageHeader prog) flags)
86         (cli,_,[]) | FlagVersion `elem` cli ->
87            bye ourCopyright
88         (cli,nonopts,[]) ->
89            case getVerbosity Normal cli of
90            Right v -> runit v cli nonopts
91            Left err -> die err
92         (_,_,errors) -> 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   | FlagForceFiles
108   | FlagAutoGHCiLibs
109   | FlagSimpleOutput
110   | FlagNamesOnly
111   | FlagIgnoreCase
112   | FlagNoUserDb
113   | FlagVerbosity (Maybe String)
114   deriving Eq
115
116 flags :: [OptDescr Flag]
117 flags = [
118   Option [] ["user"] (NoArg FlagUser)
119         "use the current user's package database",
120   Option [] ["global"] (NoArg FlagGlobal)
121         "use the global package database",
122   Option ['f'] ["package-conf"] (ReqArg FlagConfig "FILE")
123         "use the specified package config file",
124   Option [] ["global-conf"] (ReqArg FlagGlobalConfig "FILE")
125         "location of the global package config",
126   Option [] ["no-user-package-conf"] (NoArg FlagNoUserDb)
127         "never read the user package database",
128   Option [] ["force"] (NoArg FlagForce)
129          "ignore missing dependencies, directories, and libraries",
130   Option [] ["force-files"] (NoArg FlagForceFiles)
131          "ignore missing directories and libraries only",
132   Option ['g'] ["auto-ghci-libs"] (NoArg FlagAutoGHCiLibs)
133         "automatically build libs for GHCi (with register)",
134   Option ['?'] ["help"] (NoArg FlagHelp)
135         "display this help and exit",
136   Option ['V'] ["version"] (NoArg FlagVersion)
137         "output version information and exit",
138   Option [] ["simple-output"] (NoArg FlagSimpleOutput)
139         "print output in easy-to-parse format for some commands",
140   Option [] ["names-only"] (NoArg FlagNamesOnly)
141         "only print package names, not versions; can only be used with list --simple-output",
142   Option [] ["ignore-case"] (NoArg FlagIgnoreCase)
143         "ignore case for substring matching",
144   Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity")
145         "verbosity level (0-2, default 1)"
146   ]
147
148 data Verbosity = Silent | Normal | Verbose
149     deriving (Show, Eq, Ord)
150
151 getVerbosity :: Verbosity -> [Flag] -> Either String Verbosity
152 getVerbosity v [] = Right v
153 getVerbosity _ (FlagVerbosity Nothing    : fs) = getVerbosity Verbose fs
154 getVerbosity _ (FlagVerbosity (Just "0") : fs) = getVerbosity Silent  fs
155 getVerbosity _ (FlagVerbosity (Just "1") : fs) = getVerbosity Normal  fs
156 getVerbosity _ (FlagVerbosity (Just "2") : fs) = getVerbosity Verbose fs
157 getVerbosity _ (FlagVerbosity v : _) = Left ("Bad verbosity: " ++ show v)
158 getVerbosity v (_ : fs) = getVerbosity v fs
159
160 deprecFlags :: [OptDescr Flag]
161 deprecFlags = [
162         -- put deprecated flags here
163   ]
164
165 ourCopyright :: String
166 ourCopyright = "GHC package manager version " ++ Version.version ++ "\n"
167
168 usageHeader :: String -> String
169 usageHeader prog = substProg prog $
170   "Usage:\n" ++
171   "  $p register {filename | -}\n" ++
172   "    Register the package using the specified installed package\n" ++
173   "    description. The syntax for the latter is given in the $p\n" ++
174   "    documentation.\n" ++
175   "\n" ++
176   "  $p update {filename | -}\n" ++
177   "    Register the package, overwriting any other package with the\n" ++
178   "    same name.\n" ++
179   "\n" ++
180   "  $p unregister {pkg-id}\n" ++
181   "    Unregister the specified package.\n" ++
182   "\n" ++
183   "  $p expose {pkg-id}\n" ++
184   "    Expose the specified package.\n" ++
185   "\n" ++
186   "  $p hide {pkg-id}\n" ++
187   "    Hide the specified package.\n" ++
188   "\n" ++
189   "  $p list [pkg]\n" ++
190   "    List registered packages in the global database, and also the\n" ++
191   "    user database if --user is given. If a package name is given\n" ++
192   "    all the registered versions will be listed in ascending order.\n" ++
193   "    Accepts the --simple-output flag.\n" ++
194   "\n" ++
195   "  $p find-module {module}\n" ++
196   "    List registered packages exposing module {module} in the global\n" ++
197   "    database, and also the user database if --user is given.\n" ++
198   "    All the registered versions will be listed in ascending order.\n" ++
199   "    Accepts the --simple-output flag.\n" ++
200   "\n" ++
201   "  $p latest {pkg-id}\n" ++
202   "    Prints the highest registered version of a package.\n" ++
203   "\n" ++
204   "  $p check\n" ++
205   "    Check the consistency of package depenencies and list broken packages.\n" ++
206   "    Accepts the --simple-output flag.\n" ++
207   "\n" ++
208   "  $p describe {pkg}\n" ++
209   "    Give the registered description for the specified package. The\n" ++
210   "    description is returned in precisely the syntax required by $p\n" ++
211   "    register.\n" ++
212   "\n" ++
213   "  $p field {pkg} {field}\n" ++
214   "    Extract the specified field of the package description for the\n" ++
215   "    specified package. Accepts comma-separated multiple fields.\n" ++
216   "\n" ++
217   "  $p dump\n" ++
218   "    Dump the registered description for every package.  This is like\n" ++
219   "    \"ghc-pkg describe '*'\", except that it is intended to be used\n" ++
220   "    by tools that parse the results, rather than humans.\n" ++
221   "\n" ++
222   " Substring matching is supported for {module} in find-module and\n" ++
223   " for {pkg} in list, describe, and field, where a '*' indicates\n" ++
224   " open substring ends (prefix*, *suffix, *infix*).\n" ++
225   "\n" ++
226   "  When asked to modify a database (register, unregister, update,\n"++
227   "  hide, expose, and also check), ghc-pkg modifies the global database by\n"++
228   "  default.  Specifying --user causes it to act on the user database,\n"++
229   "  or --package-conf can be used to act on another database\n"++
230   "  entirely. When multiple of these options are given, the rightmost\n"++
231   "  one is used as the database to act upon.\n"++
232   "\n"++
233   "  Commands that query the package database (list, latest, describe,\n"++
234   "  field) operate on the list of databases specified by the flags\n"++
235   "  --user, --global, and --package-conf.  If none of these flags are\n"++
236   "  given, the default is --global --user.\n"++
237   "\n" ++
238   " The following optional flags are also accepted:\n"
239
240 substProg :: String -> String -> String
241 substProg _ [] = []
242 substProg prog ('$':'p':xs) = prog ++ substProg prog xs
243 substProg prog (c:xs) = c : substProg prog xs
244
245 -- -----------------------------------------------------------------------------
246 -- Do the business
247
248 data Force = NoForce | ForceFiles | ForceAll | CannotForce
249   deriving (Eq,Ord)
250
251 data PackageArg = Id PackageIdentifier | Substring String (String->Bool)
252
253 runit :: Verbosity -> [Flag] -> [String] -> IO ()
254 runit verbosity cli nonopts = do
255   installSignalHandlers -- catch ^C and clean up
256   prog <- getProgramName
257   let
258         force
259           | FlagForce `elem` cli        = ForceAll
260           | FlagForceFiles `elem` cli   = ForceFiles
261           | otherwise                   = NoForce
262         auto_ghci_libs = FlagAutoGHCiLibs `elem` cli
263         splitFields fields = unfoldr splitComma (',':fields)
264           where splitComma "" = Nothing
265                 splitComma fs = Just $ break (==',') (tail fs)
266
267         substringCheck :: String -> Maybe (String -> Bool)
268         substringCheck ""    = Nothing
269         substringCheck "*"   = Just (const True)
270         substringCheck [_]   = Nothing
271         substringCheck (h:t) =
272           case (h, init t, last t) of
273             ('*',s,'*') -> Just (isInfixOf (f s) . f)
274             ('*',_, _ ) -> Just (isSuffixOf (f t) . f)
275             ( _ ,s,'*') -> Just (isPrefixOf (f (h:s)) . f)
276             _           -> Nothing
277           where f | FlagIgnoreCase `elem` cli = map toLower
278                   | otherwise                 = id
279 #if defined(GLOB)
280         glob x | System.Info.os=="mingw32" = do
281           -- glob echoes its argument, after win32 filename globbing
282           (_,o,_,_) <- runInteractiveCommand ("glob "++x)
283           txt <- hGetContents o
284           return (read txt)
285         glob x | otherwise = return [x]
286 #endif
287   --
288   -- first, parse the command
289   case nonopts of
290 #if defined(GLOB)
291     -- dummy command to demonstrate usage and permit testing
292     -- without messing things up; use glob to selectively enable
293     -- windows filename globbing for file parameters
294     -- register, update, FlagGlobalConfig, FlagConfig; others?
295     ["glob", filename] -> do
296         print filename
297         glob filename >>= print
298 #endif
299     ["register", filename] ->
300         registerPackage filename verbosity cli auto_ghci_libs False force
301     ["update", filename] ->
302         registerPackage filename verbosity cli auto_ghci_libs True force
303     ["unregister", pkgid_str] -> do
304         pkgid <- readGlobPkgId pkgid_str
305         unregisterPackage pkgid verbosity cli force
306     ["expose", pkgid_str] -> do
307         pkgid <- readGlobPkgId pkgid_str
308         exposePackage pkgid verbosity cli force
309     ["hide",   pkgid_str] -> do
310         pkgid <- readGlobPkgId pkgid_str
311         hidePackage pkgid verbosity cli force
312     ["list"] -> do
313         listPackages cli Nothing Nothing
314     ["list", pkgid_str] ->
315         case substringCheck pkgid_str of
316           Nothing -> do pkgid <- readGlobPkgId pkgid_str
317                         listPackages cli (Just (Id pkgid)) Nothing
318           Just m -> listPackages cli (Just (Substring pkgid_str m)) Nothing
319     ["find-module", moduleName] -> do
320         let match = maybe (==moduleName) id (substringCheck moduleName)
321         listPackages cli Nothing (Just match)
322     ["latest", pkgid_str] -> do
323         pkgid <- readGlobPkgId pkgid_str
324         latestPackage cli pkgid
325     ["describe", pkgid_str] ->
326         case substringCheck pkgid_str of
327           Nothing -> do pkgid <- readGlobPkgId pkgid_str
328                         describePackage cli (Id pkgid)
329           Just m -> describePackage cli (Substring pkgid_str m)
330     ["field", pkgid_str, fields] ->
331         case substringCheck pkgid_str of
332           Nothing -> do pkgid <- readGlobPkgId pkgid_str
333                         describeField cli (Id pkgid) (splitFields fields)
334           Just m -> describeField cli (Substring pkgid_str m)
335                                       (splitFields fields)
336     ["check"] -> do
337         checkConsistency cli
338
339     ["dump"] -> do
340         dumpPackages cli
341
342     [] -> do
343         die ("missing command\n" ++
344                 usageInfo (usageHeader prog) flags)
345     (_cmd:_) -> do
346         die ("command-line syntax error\n" ++
347                 usageInfo (usageHeader prog) flags)
348
349 parseCheck :: ReadP a a -> String -> String -> IO a
350 parseCheck parser str what =
351   case [ x | (x,ys) <- readP_to_S parser str, all isSpace ys ] of
352     [x] -> return x
353     _ -> die ("cannot parse \'" ++ str ++ "\' as a " ++ what)
354
355 readGlobPkgId :: String -> IO PackageIdentifier
356 readGlobPkgId str = parseCheck parseGlobPackageId str "package identifier"
357
358 parseGlobPackageId :: ReadP r PackageIdentifier
359 parseGlobPackageId =
360   parse
361      +++
362   (do n <- parse
363       string "-*"
364       return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion }))
365
366 -- globVersion means "all versions"
367 globVersion :: Version
368 globVersion = Version{ versionBranch=[], versionTags=["*"] }
369
370 -- -----------------------------------------------------------------------------
371 -- Package databases
372
373 -- Some commands operate on a single database:
374 --      register, unregister, expose, hide
375 -- however these commands also check the union of the available databases
376 -- in order to check consistency.  For example, register will check that
377 -- dependencies exist before registering a package.
378 --
379 -- Some commands operate  on multiple databases, with overlapping semantics:
380 --      list, describe, field
381
382 type PackageDBName  = FilePath
383 type PackageDB      = [InstalledPackageInfo]
384
385 type NamedPackageDB = (PackageDBName, PackageDB)
386 type PackageDBStack = [NamedPackageDB]
387         -- A stack of package databases.  Convention: head is the topmost
388         -- in the stack.  Earlier entries override later one.
389
390 allPackagesInStack :: PackageDBStack -> [InstalledPackageInfo]
391 allPackagesInStack = concatMap snd
392
393 getPkgDatabases :: Bool -> [Flag] -> IO (PackageDBStack, Maybe PackageDBName)
394 getPkgDatabases modify my_flags = do
395   -- first we determine the location of the global package config.  On Windows,
396   -- this is found relative to the ghc-pkg.exe binary, whereas on Unix the
397   -- location is passed to the binary using the --global-config flag by the
398   -- wrapper script.
399   let err_msg = "missing --global-conf option, location of global package.conf unknown\n"
400   global_conf <-
401      case [ f | FlagGlobalConfig f <- my_flags ] of
402         [] -> do mb_dir <- getLibDir
403                  case mb_dir of
404                         Nothing  -> die err_msg
405                         Just dir ->
406                             do let path = dir </> "package.conf"
407                                exists <- doesFileExist path
408                                unless exists $ die "Can't find package.conf"
409                                return path
410         fs -> return (last fs)
411
412   let global_conf_dir = global_conf ++ ".d"
413   global_conf_dir_exists <- doesDirectoryExist global_conf_dir
414   global_confs <-
415     if global_conf_dir_exists
416       then do files <- getDirectoryContents global_conf_dir
417               return [ global_conf_dir ++ '/' : file
418                      | file <- files
419                      , isSuffixOf ".conf" file]
420       else return []
421
422   let no_user_db = FlagNoUserDb `elem` my_flags
423
424   -- get the location of the user package database, and create it if necessary
425   -- getAppUserDataDirectory can fail (e.g. if $HOME isn't set)
426   appdir <- try $ getAppUserDataDirectory "ghc"
427
428   mb_user_conf <-
429      if no_user_db then return Nothing else
430      case appdir of
431        Right dir -> do
432                let subdir = targetARCH ++ '-':targetOS ++ '-':Version.version
433                    user_conf = dir </> subdir </> "package.conf"
434                user_exists <- doesFileExist user_conf
435                return (Just (user_conf,user_exists))
436        Left _ ->
437                return Nothing
438
439   -- If the user database doesn't exist, and this command isn't a
440   -- "modify" command, then we won't attempt to create or use it.
441   let sys_databases
442         | Just (user_conf,user_exists) <- mb_user_conf,
443           modify || user_exists = user_conf : global_confs ++ [global_conf]
444         | otherwise             = global_confs ++ [global_conf]
445
446   e_pkg_path <- try (System.Environment.getEnv "GHC_PACKAGE_PATH")
447   let env_stack =
448         case e_pkg_path of
449                 Left  _ -> sys_databases
450                 Right path
451                   | last cs == ""  -> init cs ++ sys_databases
452                   | otherwise      -> cs
453                   where cs = parseSearchPath path
454
455         -- The "global" database is always the one at the bottom of the stack.
456         -- This is the database we modify by default.
457       virt_global_conf = last env_stack
458
459   let db_flags = [ f | Just f <- map is_db_flag my_flags ]
460          where is_db_flag FlagUser
461                       | Just (user_conf, _user_exists) <- mb_user_conf 
462                       = Just user_conf
463                is_db_flag FlagGlobal     = Just virt_global_conf
464                is_db_flag (FlagConfig f) = Just f
465                is_db_flag _              = Nothing
466
467   (final_stack, to_modify) <-
468      if not modify
469         then    -- For a "read" command, we use all the databases
470                 -- specified on the command line.  If there are no
471                 -- command-line flags specifying databases, the default
472                 -- is to use all the ones we know about.
473              if null db_flags then return (env_stack, Nothing)
474                               else return (reverse (nub db_flags), Nothing)
475         else let
476                 -- For a "modify" command, treat all the databases as
477                 -- a stack, where we are modifying the top one, but it
478                 -- can refer to packages in databases further down the
479                 -- stack.
480
481                 -- -f flags on the command line add to the database
482                 -- stack, unless any of them are present in the stack
483                 -- already.
484                 flag_stack = filter (`notElem` env_stack)
485                                 [ f | FlagConfig f <- reverse my_flags ]
486                                 ++ env_stack
487
488                 -- the database we actually modify is the one mentioned
489                 -- rightmost on the command-line.
490                 to_modify = if null db_flags 
491                                 then Just virt_global_conf
492                                 else Just (last db_flags)
493              in
494                 return (flag_stack, to_modify)
495
496   db_stack <- mapM (readParseDatabase mb_user_conf) final_stack
497   return (db_stack, to_modify)
498
499 readParseDatabase :: Maybe (PackageDBName,Bool)
500                   -> PackageDBName
501                   -> IO (PackageDBName,PackageDB)
502 readParseDatabase mb_user_conf filename
503   -- the user database (only) is allowed to be non-existent
504   | Just (user_conf,False) <- mb_user_conf, filename == user_conf
505   = return (filename, [])
506   | otherwise
507   = do str <- readFile filename
508        let packages = map convertPackageInfoIn $ read str
509        Exception.evaluate packages
510          `catchError` \e->
511             die ("error while parsing " ++ filename ++ ": " ++ show e)
512        return (filename,packages)
513
514 -- -----------------------------------------------------------------------------
515 -- Registering
516
517 registerPackage :: FilePath
518                 -> Verbosity
519                 -> [Flag]
520                 -> Bool              -- auto_ghci_libs
521                 -> Bool              -- update
522                 -> Force
523                 -> IO ()
524 registerPackage input verbosity my_flags auto_ghci_libs update force = do
525   (db_stack, Just to_modify) <- getPkgDatabases True my_flags
526   let
527         db_to_operate_on = my_head "register" $
528                            filter ((== to_modify).fst) db_stack
529   --
530   s <-
531     case input of
532       "-" -> do
533         when (verbosity >= Normal) $
534             putStr "Reading package info from stdin ... "
535         getContents
536       f   -> do
537         when (verbosity >= Normal) $
538             putStr ("Reading package info from " ++ show f ++ " ... ")
539         readFile f
540
541   expanded <- expandEnvVars s force
542
543   pkg <- parsePackageInfo expanded
544   when (verbosity >= Normal) $
545       putStrLn "done."
546
547   let unversioned_deps = filter (not . realVersion) (depends pkg)
548   unless (null unversioned_deps) $
549       die ("Unversioned dependencies found: " ++
550            unwords (map display unversioned_deps))
551
552   let truncated_stack = dropWhile ((/= to_modify).fst) db_stack
553   -- truncate the stack for validation, because we don't allow
554   -- packages lower in the stack to refer to those higher up.
555   validatePackageConfig pkg truncated_stack auto_ghci_libs update force
556   let new_details = filter not_this (snd db_to_operate_on) ++ [pkg]
557       not_this p = package p /= package pkg
558   writeNewConfig verbosity to_modify new_details
559
560 parsePackageInfo
561         :: String
562         -> IO InstalledPackageInfo
563 parsePackageInfo str =
564   case parseInstalledPackageInfo str of
565     ParseOk _warns ok -> return ok
566     ParseFailed err -> case locatedErrorMsg err of
567                            (Nothing, s) -> die s
568                            (Just l, s) -> die (show l ++ ": " ++ s)
569
570 -- -----------------------------------------------------------------------------
571 -- Exposing, Hiding, Unregistering are all similar
572
573 exposePackage :: PackageIdentifier -> Verbosity -> [Flag] -> Force -> IO ()
574 exposePackage = modifyPackage (\p -> [p{exposed=True}])
575
576 hidePackage :: PackageIdentifier -> Verbosity -> [Flag] -> Force -> IO ()
577 hidePackage = modifyPackage (\p -> [p{exposed=False}])
578
579 unregisterPackage :: PackageIdentifier -> Verbosity -> [Flag] -> Force -> IO ()
580 unregisterPackage = modifyPackage (\_ -> [])
581
582 modifyPackage
583   :: (InstalledPackageInfo -> [InstalledPackageInfo])
584   -> PackageIdentifier
585   -> Verbosity
586   -> [Flag]
587   -> Force
588   -> IO ()
589 modifyPackage fn pkgid verbosity my_flags force = do
590   (db_stack, Just _to_modify) <- getPkgDatabases True{-modify-} my_flags
591   ((db_name, pkgs), ps) <- fmap head $ findPackagesByDB db_stack (Id pkgid)
592 --  let ((db_name, pkgs) : rest_of_stack) = db_stack
593 --  ps <- findPackages [(db_name,pkgs)] (Id pkgid)
594   let 
595       pids = map package ps
596       modify pkg
597           | package pkg `elem` pids = fn pkg
598           | otherwise               = [pkg]
599       new_config = concat (map modify pkgs)
600
601   let
602       old_broken = brokenPackages (allPackagesInStack db_stack)
603       rest_of_stack = [ (nm, mypkgs)
604                       | (nm, mypkgs) <- db_stack, nm /= db_name ]
605       new_stack = (db_name,new_config) : rest_of_stack
606       new_broken = map package (brokenPackages (allPackagesInStack new_stack))
607       newly_broken = filter (`notElem` map package old_broken) new_broken
608   --
609   when (not (null newly_broken)) $
610       dieOrForceAll force ("unregistering " ++ display pkgid ++
611            " would break the following packages: "
612               ++ unwords (map display newly_broken))
613
614   writeNewConfig verbosity db_name new_config
615
616 -- -----------------------------------------------------------------------------
617 -- Listing packages
618
619 listPackages ::  [Flag] -> Maybe PackageArg -> Maybe (String->Bool) -> IO ()
620 listPackages my_flags mPackageName mModuleName = do
621   let simple_output = FlagSimpleOutput `elem` my_flags
622   (db_stack, _) <- getPkgDatabases False my_flags
623   let db_stack_filtered -- if a package is given, filter out all other packages
624         | Just this <- mPackageName =
625             map (\(conf,pkgs) -> (conf, filter (this `matchesPkg`) pkgs))
626                 db_stack
627         | Just match <- mModuleName = -- packages which expose mModuleName
628             map (\(conf,pkgs) -> (conf, filter (match `exposedInPkg`) pkgs))
629                 db_stack
630         | otherwise = db_stack
631
632       db_stack_sorted
633           = [ (db, sort_pkgs pkgs) | (db,pkgs) <- db_stack_filtered ]
634           where sort_pkgs = sortBy cmpPkgIds
635                 cmpPkgIds pkg1 pkg2 =
636                    case pkgName p1 `compare` pkgName p2 of
637                         LT -> LT
638                         GT -> GT
639                         EQ -> pkgVersion p1 `compare` pkgVersion p2
640                    where (p1,p2) = (package pkg1, package pkg2)
641
642       match `exposedInPkg` pkg = any match (map display $ exposedModules pkg)
643
644       pkg_map = allPackagesInStack db_stack
645       show_func = if simple_output then show_simple else mapM_ (show_normal pkg_map)
646
647   show_func (reverse db_stack_sorted)
648
649   where show_normal pkg_map (db_name,pkg_confs) =
650           hPutStrLn stdout (render $
651                 text db_name <> colon $$ nest 4 packages
652                 )
653            where packages = fsep (punctuate comma (map pp_pkg pkg_confs))
654                  broken = map package (brokenPackages pkg_map)
655                  pp_pkg p
656                    | package p `elem` broken = braces doc
657                    | exposed p = doc
658                    | otherwise = parens doc
659                    where doc = text (display (package p))
660
661         show_simple = simplePackageList my_flags . allPackagesInStack
662
663 simplePackageList :: [Flag] -> [InstalledPackageInfo] -> IO ()
664 simplePackageList my_flags pkgs = do
665    let showPkg = if FlagNamesOnly `elem` my_flags then display . pkgName
666                                                   else display
667        strs = map showPkg $ sortBy compPkgIdVer $ map package pkgs
668    when (not (null pkgs)) $
669       hPutStrLn stdout $ concat $ intersperse " " strs
670
671 -- -----------------------------------------------------------------------------
672 -- Prints the highest (hidden or exposed) version of a package
673
674 latestPackage ::  [Flag] -> PackageIdentifier -> IO ()
675 latestPackage my_flags pkgid = do
676   (db_stack, _) <- getPkgDatabases False my_flags
677   ps <- findPackages db_stack (Id pkgid)
678   show_pkg (sortBy compPkgIdVer (map package ps))
679   where
680     show_pkg [] = die "no matches"
681     show_pkg pids = hPutStrLn stdout (display (last pids))
682
683 -- -----------------------------------------------------------------------------
684 -- Describe
685
686 describePackage :: [Flag] -> PackageArg -> IO ()
687 describePackage my_flags pkgarg = do
688   (db_stack, _) <- getPkgDatabases False my_flags
689   ps <- findPackages db_stack pkgarg
690   doDump ps
691
692 dumpPackages :: [Flag] -> IO ()
693 dumpPackages my_flags = do
694   (db_stack, _) <- getPkgDatabases False my_flags
695   doDump (allPackagesInStack db_stack)
696
697 doDump :: [InstalledPackageInfo] -> IO ()
698 doDump = mapM_ putStrLn . intersperse "---" . map showInstalledPackageInfo
699
700 -- PackageId is can have globVersion for the version
701 findPackages :: PackageDBStack -> PackageArg -> IO [InstalledPackageInfo]
702 findPackages db_stack pkgarg
703   = fmap (concatMap snd) $ findPackagesByDB db_stack pkgarg
704
705 findPackagesByDB :: PackageDBStack -> PackageArg
706                  -> IO [(NamedPackageDB, [InstalledPackageInfo])]
707 findPackagesByDB db_stack pkgarg
708   = case [ (db, matched)
709          | db@(_, pkgs) <- db_stack,
710            let matched = filter (pkgarg `matchesPkg`) pkgs,
711            not (null matched) ] of
712         [] -> die ("cannot find package " ++ pkg_msg pkgarg)
713         ps -> return ps
714   where
715         pkg_msg (Id pkgid)           = display pkgid
716         pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat
717
718 matches :: PackageIdentifier -> PackageIdentifier -> Bool
719 pid `matches` pid'
720   = (pkgName pid == pkgName pid')
721     && (pkgVersion pid == pkgVersion pid' || not (realVersion pid))
722
723 matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool
724 (Id pid)        `matchesPkg` pkg = pid `matches` package pkg
725 (Substring _ m) `matchesPkg` pkg = m (display (package pkg))
726
727 compPkgIdVer :: PackageIdentifier -> PackageIdentifier -> Ordering
728 compPkgIdVer p1 p2 = pkgVersion p1 `compare` pkgVersion p2
729
730 -- -----------------------------------------------------------------------------
731 -- Field
732
733 describeField :: [Flag] -> PackageArg -> [String] -> IO ()
734 describeField my_flags pkgarg fields = do
735   (db_stack, _) <- getPkgDatabases False my_flags
736   fns <- toFields fields
737   ps <- findPackages db_stack pkgarg
738   let top_dir = takeDirectory (fst (last db_stack))
739   mapM_ (selectFields fns) (mungePackagePaths top_dir ps)
740   where toFields [] = return []
741         toFields (f:fs) = case toField f of
742             Nothing -> die ("unknown field: " ++ f)
743             Just fn -> do fns <- toFields fs
744                           return (fn:fns)
745         selectFields fns info = mapM_ (\fn->putStrLn (fn info)) fns
746
747 mungePackagePaths :: String -> [InstalledPackageInfo] -> [InstalledPackageInfo]
748 -- Replace the strings "$topdir" and "$httptopdir" at the beginning of a path
749 -- with the current topdir (obtained from the -B option).
750 mungePackagePaths top_dir ps = map munge_pkg ps
751   where
752   munge_pkg p = p{ importDirs        = munge_paths (importDirs p),
753                    includeDirs       = munge_paths (includeDirs p),
754                    libraryDirs       = munge_paths (libraryDirs p),
755                    frameworkDirs     = munge_paths (frameworkDirs p),
756                    haddockInterfaces = munge_paths (haddockInterfaces p),
757                    haddockHTMLs      = munge_paths (haddockHTMLs p)
758                  }
759
760   munge_paths = map munge_path
761
762   munge_path p
763    | Just p' <- maybePrefixMatch "$topdir"     p =            top_dir ++ p'
764    | Just p' <- maybePrefixMatch "$httptopdir" p = toHttpPath top_dir ++ p'
765    | otherwise                               = p
766
767   toHttpPath p = "file:///" ++ p
768
769 maybePrefixMatch :: String -> String -> Maybe String
770 maybePrefixMatch []    rest = Just rest
771 maybePrefixMatch (_:_) []   = Nothing
772 maybePrefixMatch (p:pat) (r:rest)
773   | p == r    = maybePrefixMatch pat rest
774   | otherwise = Nothing
775
776 toField :: String -> Maybe (InstalledPackageInfo -> String)
777 -- backwards compatibility:
778 toField "import_dirs"     = Just $ strList . importDirs
779 toField "source_dirs"     = Just $ strList . importDirs
780 toField "library_dirs"    = Just $ strList . libraryDirs
781 toField "hs_libraries"    = Just $ strList . hsLibraries
782 toField "extra_libraries" = Just $ strList . extraLibraries
783 toField "include_dirs"    = Just $ strList . includeDirs
784 toField "c_includes"      = Just $ strList . includes
785 toField "package_deps"    = Just $ strList . map display. depends
786 toField "extra_cc_opts"   = Just $ strList . ccOptions
787 toField "extra_ld_opts"   = Just $ strList . ldOptions
788 toField "framework_dirs"  = Just $ strList . frameworkDirs
789 toField "extra_frameworks"= Just $ strList . frameworks
790 toField s                 = showInstalledPackageInfoField s
791
792 strList :: [String] -> String
793 strList = show
794
795
796 -- -----------------------------------------------------------------------------
797 -- Check: Check consistency of installed packages
798
799 checkConsistency :: [Flag] -> IO ()
800 checkConsistency my_flags = do
801   (db_stack, _) <- getPkgDatabases True my_flags
802          -- check behaves like modify for the purposes of deciding which
803          -- databases to use, because ordering is important.
804
805   let simple_output = FlagSimpleOutput `elem` my_flags
806
807   let pkgs = allPackagesInStack db_stack
808
809       checkPackage p = do
810          (_,es) <- runValidate $ checkPackageConfig p db_stack False True
811          if null es
812             then return []
813             else do
814               when (not simple_output) $ do
815                   reportError ("There are problems in package " ++ display (package p) ++ ":")
816                   reportValidateErrors es "  " Nothing
817                   return ()
818               return [p]
819
820   broken_pkgs <- concat `fmap` mapM checkPackage pkgs
821
822   let filterOut pkgs1 pkgs2 = filter not_in pkgs2
823         where not_in p = package p `notElem` all_ps
824               all_ps = map package pkgs1
825
826   let not_broken_pkgs = filterOut broken_pkgs pkgs
827       (_, trans_broken_pkgs) = closure [] not_broken_pkgs
828       all_broken_pkgs = broken_pkgs ++ trans_broken_pkgs
829
830   when (not (null all_broken_pkgs)) $ do
831     if simple_output
832       then simplePackageList my_flags all_broken_pkgs
833       else do
834        reportError ("\nThe following packages are broken, either because they have a problem\n"++
835                 "listed above, or because they depend on a broken package.")
836        mapM_ (hPutStrLn stderr . display . package) all_broken_pkgs
837
838   when (not (null all_broken_pkgs)) $ exitWith (ExitFailure 1)
839
840
841 closure :: [InstalledPackageInfo] -> [InstalledPackageInfo]
842         -> ([InstalledPackageInfo], [InstalledPackageInfo])
843 closure pkgs db_stack = go pkgs db_stack
844  where
845    go avail not_avail =
846      case partition (depsAvailable avail) not_avail of
847         ([],        not_avail') -> (avail, not_avail')
848         (new_avail, not_avail') -> go (new_avail ++ avail) not_avail'
849
850    depsAvailable :: [InstalledPackageInfo] -> InstalledPackageInfo
851                  -> Bool
852    depsAvailable pkgs_ok pkg = null dangling
853         where dangling = filter (`notElem` pids) (depends pkg)
854               pids = map package pkgs_ok
855
856         -- we want mutually recursive groups of package to show up
857         -- as broken. (#1750)
858
859 brokenPackages :: [InstalledPackageInfo] -> [InstalledPackageInfo]
860 brokenPackages pkgs = snd (closure [] pkgs)
861
862 -- -----------------------------------------------------------------------------
863 -- Manipulating package.conf files
864
865 type InstalledPackageInfoString = InstalledPackageInfo_ String
866
867 convertPackageInfoOut :: InstalledPackageInfo -> InstalledPackageInfoString
868 convertPackageInfoOut
869     (pkgconf@(InstalledPackageInfo { exposedModules = e,
870                                      hiddenModules = h })) =
871         pkgconf{ exposedModules = map display e,
872                  hiddenModules  = map display h }
873
874 convertPackageInfoIn :: InstalledPackageInfoString -> InstalledPackageInfo
875 convertPackageInfoIn
876     (pkgconf@(InstalledPackageInfo { exposedModules = e,
877                                      hiddenModules = h })) =
878         pkgconf{ exposedModules = map convert e,
879                  hiddenModules  = map convert h }
880     where convert = fromJust . simpleParse
881
882 writeNewConfig :: Verbosity -> FilePath -> [InstalledPackageInfo] -> IO ()
883 writeNewConfig verbosity filename packages = do
884   when (verbosity >= Normal) $
885       hPutStr stdout "Writing new package config file... "
886   createDirectoryIfMissing True $ takeDirectory filename
887   let shown = concat $ intersperse ",\n "
888                      $ map (show . convertPackageInfoOut) packages
889       fileContents = "[" ++ shown ++ "\n]"
890   writeFileAtomic filename fileContents
891     `catch` \e ->
892       if isPermissionError e
893       then die (filename ++ ": you don't have permission to modify this file")
894       else ioError e
895   when (verbosity >= Normal) $
896       hPutStrLn stdout "done."
897
898 -----------------------------------------------------------------------------
899 -- Sanity-check a new package config, and automatically build GHCi libs
900 -- if requested.
901
902 type ValidateError = (Force,String)
903
904 newtype Validate a = V { runValidate :: IO (a, [ValidateError]) }
905
906 instance Monad Validate where
907    return a = V $ return (a, [])
908    m >>= k = V $ do
909       (a, es) <- runValidate m
910       (b, es') <- runValidate (k a)
911       return (b,es++es')
912
913 verror :: Force -> String -> Validate ()
914 verror f s = V (return ((),[(f,s)]))
915
916 liftIO :: IO a -> Validate a
917 liftIO k = V (k >>= \a -> return (a,[]))
918
919 -- returns False if we should die
920 reportValidateErrors :: [ValidateError] -> String -> Maybe Force -> IO Bool
921 reportValidateErrors es prefix mb_force = do
922   oks <- mapM report es
923   return (and oks)
924   where
925     report (f,s)
926       | Just force <- mb_force
927       = if (force >= f)
928            then do reportError (prefix ++ s ++ " (ignoring)")
929                    return True
930            else if f < CannotForce
931                    then do reportError (prefix ++ s ++ " (use --force to override)")
932                            return False
933                    else do reportError err
934                            return False
935       | otherwise = do reportError err
936                        return False
937       where
938              err = prefix ++ s
939
940 validatePackageConfig :: InstalledPackageInfo
941                       -> PackageDBStack
942                       -> Bool   -- auto-ghc-libs
943                       -> Bool   -- update, or check
944                       -> Force
945                       -> IO ()
946 validatePackageConfig pkg db_stack auto_ghci_libs update force = do
947   (_,es) <- runValidate $ checkPackageConfig pkg db_stack auto_ghci_libs update
948   ok <- reportValidateErrors es (display (package pkg) ++ ": ") (Just force)
949   when (not ok) $ exitWith (ExitFailure 1)
950
951 checkPackageConfig :: InstalledPackageInfo
952                       -> PackageDBStack
953                       -> Bool   -- auto-ghc-libs
954                       -> Bool   -- update, or check
955                       -> Validate ()
956 checkPackageConfig pkg db_stack auto_ghci_libs update = do
957   checkPackageId pkg
958   checkDuplicates db_stack pkg update
959   mapM_ (checkDep db_stack) (depends pkg)
960   checkDuplicateDepends (depends pkg)
961   mapM_ (checkDir "import-dirs") (importDirs pkg)
962   mapM_ (checkDir "library-dirs") (libraryDirs pkg)
963   mapM_ (checkDir "include-dirs") (includeDirs pkg)
964   checkModules pkg
965   mapM_ (checkHSLib (libraryDirs pkg) auto_ghci_libs) (hsLibraries pkg)
966   -- ToDo: check these somehow?
967   --    extra_libraries :: [String],
968   --    c_includes      :: [String],
969
970 -- When the package name and version are put together, sometimes we can
971 -- end up with a package id that cannot be parsed.  This will lead to
972 -- difficulties when the user wants to refer to the package later, so
973 -- we check that the package id can be parsed properly here.
974 checkPackageId :: InstalledPackageInfo -> Validate ()
975 checkPackageId ipi =
976   let str = display (package ipi) in
977   case [ x :: PackageIdentifier | (x,ys) <- readP_to_S parse str, all isSpace ys ] of
978     [_] -> return ()
979     []  -> verror CannotForce ("invalid package identifier: " ++ str)
980     _   -> verror CannotForce ("ambiguous package identifier: " ++ str)
981
982 checkDuplicates :: PackageDBStack -> InstalledPackageInfo -> Bool -> Validate ()
983 checkDuplicates db_stack pkg update = do
984   let
985         pkgid = package pkg
986         (_top_db_name, pkgs) : _  = db_stack
987   --
988   -- Check whether this package id already exists in this DB
989   --
990   when (not update && (pkgid `elem` map package pkgs)) $
991        verror CannotForce $
992           "package " ++ display pkgid ++ " is already installed"
993
994   let
995         uncasep = map toLower . display
996         dups = filter ((== uncasep pkgid) . uncasep) (map package pkgs)
997
998   when (not update && not (null dups)) $ verror ForceAll $
999         "Package names may be treated case-insensitively in the future.\n"++
1000         "Package " ++ display pkgid ++
1001         " overlaps with: " ++ unwords (map display dups)
1002
1003
1004 checkDir :: String -> String -> Validate ()
1005 checkDir thisfield d
1006  | "$topdir"     `isPrefixOf` d = return ()
1007  | "$httptopdir" `isPrefixOf` d = return ()
1008         -- can't check these, because we don't know what $(http)topdir is
1009  | otherwise = do
1010    there <- liftIO $ doesDirectoryExist d
1011    when (not there) $
1012        verror ForceFiles (thisfield ++ ": " ++ d ++ " doesn't exist or isn't a directory")
1013
1014 checkDep :: PackageDBStack -> PackageIdentifier -> Validate ()
1015 checkDep db_stack pkgid
1016   | pkgid `elem` pkgids || (not real_version && name_exists) = return ()
1017   | otherwise = verror ForceAll ("dependency " ++ display pkgid
1018                                  ++ " doesn't exist")
1019   where
1020         -- for backwards compat, we treat 0.0 as a special version,
1021         -- and don't check that it actually exists.
1022         real_version = realVersion pkgid
1023
1024         name_exists = any (\p -> pkgName (package p) == name) all_pkgs
1025         name = pkgName pkgid
1026
1027         all_pkgs = allPackagesInStack db_stack
1028         pkgids = map package all_pkgs
1029
1030 checkDuplicateDepends :: [PackageIdentifier] -> Validate ()
1031 checkDuplicateDepends deps
1032   | null dups = return ()
1033   | otherwise = verror ForceAll ("package has duplicate dependencies: " ++
1034                                      unwords (map display dups))
1035   where
1036        dups = [ p | (p:_:_) <- group (sort deps) ]
1037
1038 realVersion :: PackageIdentifier -> Bool
1039 realVersion pkgid = versionBranch (pkgVersion pkgid) /= []
1040
1041 checkHSLib :: [String] -> Bool -> String -> Validate ()
1042 checkHSLib dirs auto_ghci_libs lib = do
1043   let batch_lib_file = "lib" ++ lib ++ ".a"
1044   m <- liftIO $ doesFileExistOnPath batch_lib_file dirs
1045   case m of
1046     Nothing -> verror ForceFiles ("cannot find " ++ batch_lib_file ++
1047                                    " on library path")
1048     Just dir -> liftIO $ checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
1049
1050 doesFileExistOnPath :: String -> [FilePath] -> IO (Maybe FilePath)
1051 doesFileExistOnPath file path = go path
1052   where go []     = return Nothing
1053         go (p:ps) = do b <- doesFileExistIn file p
1054                        if b then return (Just p) else go ps
1055
1056 doesFileExistIn :: String -> String -> IO Bool
1057 doesFileExistIn lib d
1058  | "$topdir"     `isPrefixOf` d = return True
1059  | "$httptopdir" `isPrefixOf` d = return True
1060  | otherwise                = doesFileExist (d </> lib)
1061
1062 checkModules :: InstalledPackageInfo -> Validate ()
1063 checkModules pkg = do
1064   mapM_ findModule (exposedModules pkg ++ hiddenModules pkg)
1065   where
1066     findModule modl = do
1067       -- there's no .hi file for GHC.Prim
1068       if modl == fromString "GHC.Prim" then return () else do
1069       let file = toFilePath modl <.> "hi"
1070       m <- liftIO $ doesFileExistOnPath file (importDirs pkg)
1071       when (isNothing m) $
1072          verror ForceFiles ("file " ++ file ++ " is missing")
1073
1074 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
1075 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build
1076   | auto_build = autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
1077   | otherwise  = do
1078       m <- doesFileExistOnPath ghci_lib_file dirs
1079       when (isNothing m && ghci_lib_file /= "HSrts.o") $
1080         hPutStrLn stderr ("warning: can't find GHCi lib " ++ ghci_lib_file)
1081  where
1082     ghci_lib_file = lib <.> "o"
1083
1084 -- automatically build the GHCi version of a batch lib,
1085 -- using ld --whole-archive.
1086
1087 autoBuildGHCiLib :: String -> String -> String -> IO ()
1088 autoBuildGHCiLib dir batch_file ghci_file = do
1089   let ghci_lib_file  = dir ++ '/':ghci_file
1090       batch_lib_file = dir ++ '/':batch_file
1091   hPutStr stderr ("building GHCi library " ++ ghci_lib_file ++ "...")
1092 #if defined(darwin_HOST_OS)
1093   r <- rawSystem "ld" ["-r","-x","-o",ghci_lib_file,"-all_load",batch_lib_file]
1094 #elif defined(mingw32_HOST_OS)
1095   execDir <- getLibDir
1096   r <- rawSystem (maybe "" (++"/gcc-lib/") execDir++"ld") ["-r","-x","-o",ghci_lib_file,"--whole-archive",batch_lib_file]
1097 #else
1098   r <- rawSystem "ld" ["-r","-x","-o",ghci_lib_file,"--whole-archive",batch_lib_file]
1099 #endif
1100   when (r /= ExitSuccess) $ exitWith r
1101   hPutStrLn stderr (" done.")
1102
1103 -- -----------------------------------------------------------------------------
1104 -- Searching for modules
1105
1106 #if not_yet
1107
1108 findModules :: [FilePath] -> IO [String]
1109 findModules paths =
1110   mms <- mapM searchDir paths
1111   return (concat mms)
1112
1113 searchDir path prefix = do
1114   fs <- getDirectoryEntries path `catch` \_ -> return []
1115   searchEntries path prefix fs
1116
1117 searchEntries path prefix [] = return []
1118 searchEntries path prefix (f:fs)
1119   | looks_like_a_module  =  do
1120         ms <- searchEntries path prefix fs
1121         return (prefix `joinModule` f : ms)
1122   | looks_like_a_component  =  do
1123         ms <- searchDir (path </> f) (prefix `joinModule` f)
1124         ms' <- searchEntries path prefix fs
1125         return (ms ++ ms')
1126   | otherwise
1127         searchEntries path prefix fs
1128
1129   where
1130         (base,suffix) = splitFileExt f
1131         looks_like_a_module =
1132                 suffix `elem` haskell_suffixes &&
1133                 all okInModuleName base
1134         looks_like_a_component =
1135                 null suffix && all okInModuleName base
1136
1137 okInModuleName c
1138
1139 #endif
1140
1141 -- ---------------------------------------------------------------------------
1142 -- expanding environment variables in the package configuration
1143
1144 expandEnvVars :: String -> Force -> IO String
1145 expandEnvVars str0 force = go str0 ""
1146  where
1147    go "" acc = return $! reverse acc
1148    go ('$':'{':str) acc | (var, '}':rest) <- break close str
1149         = do value <- lookupEnvVar var
1150              go rest (reverse value ++ acc)
1151         where close c = c == '}' || c == '\n' -- don't span newlines
1152    go (c:str) acc
1153         = go str (c:acc)
1154
1155    lookupEnvVar :: String -> IO String
1156    lookupEnvVar nm =
1157         catch (System.Environment.getEnv nm)
1158            (\ _ -> do dieOrForceAll force ("Unable to expand variable " ++
1159                                         show nm)
1160                       return "")
1161
1162 -----------------------------------------------------------------------------
1163
1164 getProgramName :: IO String
1165 getProgramName = liftM (`withoutSuffix` ".bin") getProgName
1166    where str `withoutSuffix` suff
1167             | suff `isSuffixOf` str = take (length str - length suff) str
1168             | otherwise             = str
1169
1170 bye :: String -> IO a
1171 bye s = putStr s >> exitWith ExitSuccess
1172
1173 die :: String -> IO a
1174 die = dieWith 1
1175
1176 dieWith :: Int -> String -> IO a
1177 dieWith ec s = do
1178   hFlush stdout
1179   prog <- getProgramName
1180   hPutStrLn stderr (prog ++ ": " ++ s)
1181   exitWith (ExitFailure ec)
1182
1183 dieOrForceAll :: Force -> String -> IO ()
1184 dieOrForceAll ForceAll s = ignoreError s
1185 dieOrForceAll _other s   = dieForcible s
1186
1187 ignoreError :: String -> IO ()
1188 ignoreError s = reportError (s ++ " (ignoring)")
1189
1190 reportError :: String -> IO ()
1191 reportError s = do hFlush stdout; hPutStrLn stderr s
1192
1193 dieForcible :: String -> IO ()
1194 dieForcible s = die (s ++ " (use --force to override)")
1195
1196 my_head :: String -> [a] -> a
1197 my_head s []      = error s
1198 my_head _ (x : _) = x
1199
1200 -----------------------------------------
1201 -- Cut and pasted from ghc/compiler/main/SysTools
1202
1203 #if defined(mingw32_HOST_OS)
1204 subst :: Char -> Char -> String -> String
1205 subst a b ls = map (\ x -> if x == a then b else x) ls
1206
1207 unDosifyPath :: FilePath -> FilePath
1208 unDosifyPath xs = subst '\\' '/' xs
1209
1210 getLibDir :: IO (Maybe String)
1211 getLibDir = fmap (fmap (</> "lib")) $ getExecDir "/bin/ghc-pkg.exe"
1212
1213 -- (getExecDir cmd) returns the directory in which the current
1214 --                  executable, which should be called 'cmd', is running
1215 -- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
1216 -- you'll get "/a/b/c" back as the result
1217 getExecDir :: String -> IO (Maybe String)
1218 getExecDir cmd =
1219     getExecPath >>= maybe (return Nothing) removeCmdSuffix
1220     where initN n = reverse . drop n . reverse
1221           removeCmdSuffix = return . Just . initN (length cmd) . unDosifyPath
1222
1223 getExecPath :: IO (Maybe String)
1224 getExecPath =
1225      allocaArray len $ \buf -> do
1226          ret <- getModuleFileName nullPtr buf len
1227          if ret == 0 then return Nothing
1228                      else liftM Just $ peekCString buf
1229     where len = 2048 -- Plenty, PATH_MAX is 512 under Win32.
1230
1231 foreign import stdcall unsafe "GetModuleFileNameA"
1232     getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
1233
1234 #else
1235 getLibDir :: IO (Maybe String)
1236 getLibDir = return Nothing
1237 #endif
1238
1239 -----------------------------------------
1240 -- Adapted from ghc/compiler/utils/Panic
1241
1242 installSignalHandlers :: IO ()
1243 installSignalHandlers = do
1244   threadid <- myThreadId
1245   let
1246       interrupt = Exception.throwTo threadid
1247                                     (Exception.ErrorCall "interrupted")
1248   --
1249 #if !defined(mingw32_HOST_OS)
1250   installHandler sigQUIT (Catch interrupt) Nothing
1251   installHandler sigINT  (Catch interrupt) Nothing
1252   return ()
1253 #elif __GLASGOW_HASKELL__ >= 603
1254   -- GHC 6.3+ has support for console events on Windows
1255   -- NOTE: running GHCi under a bash shell for some reason requires
1256   -- you to press Ctrl-Break rather than Ctrl-C to provoke
1257   -- an interrupt.  Ctrl-C is getting blocked somewhere, I don't know
1258   -- why --SDM 17/12/2004
1259   let sig_handler ControlC = interrupt
1260       sig_handler Break    = interrupt
1261       sig_handler _        = return ()
1262
1263   installHandler (Catch sig_handler)
1264   return ()
1265 #else
1266   return () -- nothing
1267 #endif
1268
1269 #if __GLASGOW_HASKELL__ <= 604
1270 isInfixOf               :: (Eq a) => [a] -> [a] -> Bool
1271 isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
1272 #endif
1273
1274 #if mingw32_HOST_OS || mingw32_TARGET_OS
1275 throwIOIO :: Exception.IOException -> IO a
1276 throwIOIO = Exception.throwIO
1277
1278 catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a
1279 catchIO = Exception.catch
1280 #endif
1281
1282 catchError :: IO a -> (String -> IO a) -> IO a
1283 catchError io handler = io `Exception.catch` handler'
1284     where handler' (Exception.ErrorCall err) = handler err
1285
1286
1287 -- copied from Cabal's Distribution.Simple.Utils, except that we want
1288 -- to use text files here, rather than binary files.
1289 writeFileAtomic :: FilePath -> String -> IO ()
1290 writeFileAtomic targetFile content = do
1291   (newFile, newHandle) <- openNewFile targetDir template
1292   do  hPutStr newHandle content
1293       hClose newHandle
1294 #if mingw32_HOST_OS || mingw32_TARGET_OS
1295       renameFile newFile targetFile
1296         -- If the targetFile exists then renameFile will fail
1297         `catchIO` \err -> do
1298           exists <- doesFileExist targetFile
1299           if exists
1300             then do removeFile targetFile
1301                     -- Big fat hairy race condition
1302                     renameFile newFile targetFile
1303                     -- If the removeFile succeeds and the renameFile fails
1304                     -- then we've lost the atomic property.
1305             else throwIOIO err
1306 #else
1307       renameFile newFile targetFile
1308 #endif
1309    `Exception.onException` do hClose newHandle
1310                               removeFile newFile
1311   where
1312     template = targetName <.> "tmp"
1313     targetDir | null targetDir_ = "."
1314               | otherwise       = targetDir_
1315     --TODO: remove this when takeDirectory/splitFileName is fixed
1316     --      to always return a valid dir
1317     (targetDir_,targetName) = splitFileName targetFile
1318
1319 -- Ugh, this is a copy/paste of code from the base library, but
1320 -- if uses 666 rather than 600 for the permissions.
1321 openNewFile :: FilePath -> String -> IO (FilePath, Handle)
1322 openNewFile dir template = do
1323   pid <- c_getpid
1324   findTempName pid
1325   where
1326     -- We split off the last extension, so we can use .foo.ext files
1327     -- for temporary files (hidden on Unix OSes). Unfortunately we're
1328     -- below filepath in the hierarchy here.
1329     (prefix,suffix) =
1330        case break (== '.') $ reverse template of
1331          -- First case: template contains no '.'s. Just re-reverse it.
1332          (rev_suffix, "")       -> (reverse rev_suffix, "")
1333          -- Second case: template contains at least one '.'. Strip the
1334          -- dot from the prefix and prepend it to the suffix (if we don't
1335          -- do this, the unique number will get added after the '.' and
1336          -- thus be part of the extension, which is wrong.)
1337          (rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
1338          -- Otherwise, something is wrong, because (break (== '.')) should
1339          -- always return a pair with either the empty string or a string
1340          -- beginning with '.' as the second component.
1341          _                      -> error "bug in System.IO.openTempFile"
1342
1343     oflags = rw_flags .|. o_EXCL
1344
1345 #if __GLASGOW_HASKELL__ < 611
1346     withFilePath = withCString
1347 #endif
1348
1349     findTempName x = do
1350       fd <- withFilePath filepath $ \ f ->
1351               c_open f oflags 0o666
1352       if fd < 0
1353        then do
1354          errno <- getErrno
1355          if errno == eEXIST
1356            then findTempName (x+1)
1357            else ioError (errnoToIOError "openNewBinaryFile" errno Nothing (Just dir))
1358        else do
1359          -- XXX We want to tell fdToHandle what the filepath is,
1360          -- as any exceptions etc will only be able to report the
1361          -- fd currently
1362          h <-
1363 #if __GLASGOW_HASKELL__ >= 609
1364               fdToHandle fd
1365 #else
1366               fdToHandle (fromIntegral fd)
1367 #endif
1368               `Exception.onException` c_close fd
1369          return (filepath, h)
1370       where
1371         filename        = prefix ++ show x ++ suffix
1372         filepath        = dir `combine` filename
1373
1374 -- XXX Copied from GHC.Handle
1375 std_flags, output_flags, rw_flags :: CInt
1376 std_flags    = o_NONBLOCK   .|. o_NOCTTY
1377 output_flags = std_flags    .|. o_CREAT
1378 rw_flags     = output_flags .|. o_RDWR
1379
1380 -- | The function splits the given string to substrings
1381 -- using 'isSearchPathSeparator'.
1382 parseSearchPath :: String -> [FilePath]
1383 parseSearchPath path = split path
1384   where
1385     split :: String -> [String]
1386     split s =
1387       case rest' of
1388         []     -> [chunk]
1389         _:rest -> chunk : split rest
1390       where
1391         chunk =
1392           case chunk' of
1393 #ifdef mingw32_HOST_OS
1394             ('\"':xs@(_:_)) | last xs == '\"' -> init xs
1395 #endif
1396             _                                 -> chunk'
1397
1398         (chunk', rest') = break isSearchPathSeparator s