1 {-# LANGUAGE PatternGuards, CPP, ForeignFunctionInterface #-}
2 -----------------------------------------------------------------------------
4 -- (c) The University of Glasgow 2004-2009.
6 -- Package management tool
8 -----------------------------------------------------------------------------
10 module Main (main) where
12 import Version ( version, targetOS, targetARCH )
13 import Distribution.InstalledPackageInfo.Binary()
14 import qualified Distribution.Simple.PackageIndex as PackageIndex
15 import Distribution.ModuleName hiding (main)
16 import Distribution.InstalledPackageInfo
17 import Distribution.Compat.ReadP
18 import Distribution.ParseUtils
19 import Distribution.Package hiding (depends)
20 import Distribution.Text
21 import Distribution.Version
22 import System.FilePath
23 import System.Cmd ( rawSystem )
24 import System.Directory ( getAppUserDataDirectory, createDirectoryIfMissing,
30 import System.Console.GetOpt
31 import qualified Control.Exception as Exception
34 import Data.Char ( isSpace, toLower )
36 import System.Directory ( doesDirectoryExist, getDirectoryContents,
37 doesFileExist, renameFile, removeFile )
38 import System.Exit ( exitWith, ExitCode(..) )
39 import System.Environment ( getArgs, getProgName, getEnv )
41 import System.IO.Error
43 import Control.Concurrent
45 import qualified Data.ByteString.Lazy as B
46 import qualified Data.Binary as Bin
47 import qualified Data.Binary.Get as Bin
49 #if __GLASGOW_HASKELL__ < 612 || defined(mingw32_HOST_OS)
50 -- mingw32 needs these for getExecDir, GHC <6.12 needs them for openNewFile
55 #if __GLASGOW_HASKELL__ < 612
56 import System.Posix.Internals
57 import GHC.Handle (fdToHandle)
60 #ifdef mingw32_HOST_OS
61 import GHC.ConsoleHandler
63 import System.Posix hiding (fdToHandle)
67 import System.Process(runInteractiveCommand)
68 import qualified System.Info(os)
71 #if !defined(mingw32_HOST_OS) && __GLASGOW_HASKELL__ >= 611 && !defined(BOOTSTRAPPING)
72 import System.Console.Terminfo as Terminfo
75 -- -----------------------------------------------------------------------------
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 ->
89 case getVerbosity Normal cli of
90 Right v -> runit v cli nonopts
93 prog <- getProgramName
94 die (concat errors ++ usageInfo (usageHeader prog) flags)
96 -- -----------------------------------------------------------------------------
97 -- Command-line syntax
104 | FlagConfig FilePath
105 | FlagGlobalConfig FilePath
113 | FlagVerbosity (Maybe String)
116 flags :: [OptDescr Flag]
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)"
148 data Verbosity = Silent | Normal | Verbose
149 deriving (Show, Eq, Ord)
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
160 deprecFlags :: [OptDescr Flag]
162 -- put deprecated flags here
165 ourCopyright :: String
166 ourCopyright = "GHC package manager version " ++ Version.version ++ "\n"
168 usageHeader :: String -> String
169 usageHeader prog = substProg prog $
171 " $p init {path}\n" ++
172 " Create and initialise a package database at the location {path}.\n" ++
173 " Packages can be registered in the new database using the register\n" ++
174 " command with --package-conf={path}. To use the new database with GHC,\n" ++
175 " use GHC's -package-conf flag.\n" ++
177 " $p register {filename | -}\n" ++
178 " Register the package using the specified installed package\n" ++
179 " description. The syntax for the latter is given in the $p\n" ++
180 " documentation. The input file should be encoded in UTF-8.\n" ++
182 " $p update {filename | -}\n" ++
183 " Register the package, overwriting any other package with the\n" ++
184 " same name. The input file should be encoded in UTF-8.\n" ++
186 " $p unregister {pkg-id}\n" ++
187 " Unregister the specified package.\n" ++
189 " $p expose {pkg-id}\n" ++
190 " Expose the specified package.\n" ++
192 " $p hide {pkg-id}\n" ++
193 " Hide the specified package.\n" ++
195 " $p list [pkg]\n" ++
196 " List registered packages in the global database, and also the\n" ++
197 " user database if --user is given. If a package name is given\n" ++
198 " all the registered versions will be listed in ascending order.\n" ++
199 " Accepts the --simple-output flag.\n" ++
202 " Generate a graph of the package dependencies in a form suitable\n" ++
203 " for input for the graphviz tools. For example, to generate a PDF" ++
204 " of the dependency graph: ghc-pkg dot | tred | dot -Tpdf >pkgs.pdf" ++
206 " $p find-module {module}\n" ++
207 " List registered packages exposing module {module} in the global\n" ++
208 " database, and also the user database if --user is given.\n" ++
209 " All the registered versions will be listed in ascending order.\n" ++
210 " Accepts the --simple-output flag.\n" ++
212 " $p latest {pkg-id}\n" ++
213 " Prints the highest registered version of a package.\n" ++
216 " Check the consistency of package depenencies and list broken packages.\n" ++
217 " Accepts the --simple-output flag.\n" ++
219 " $p describe {pkg}\n" ++
220 " Give the registered description for the specified package. The\n" ++
221 " description is returned in precisely the syntax required by $p\n" ++
224 " $p field {pkg} {field}\n" ++
225 " Extract the specified field of the package description for the\n" ++
226 " specified package. Accepts comma-separated multiple fields.\n" ++
229 " Dump the registered description for every package. This is like\n" ++
230 " \"ghc-pkg describe '*'\", except that it is intended to be used\n" ++
231 " by tools that parse the results, rather than humans. The output is\n" ++
232 " always encoded in UTF-8, regardless of the current locale.\n" ++
235 " Regenerate the package database cache. This command should only be\n" ++
236 " necessary if you added a package to the database by dropping a file\n" ++
237 " into the database directory manually. By default, the global DB\n" ++
238 " is recached; to recache a different DB use --user or --package-conf\n" ++
239 " as appropriate.\n" ++
241 " Substring matching is supported for {module} in find-module and\n" ++
242 " for {pkg} in list, describe, and field, where a '*' indicates\n" ++
243 " open substring ends (prefix*, *suffix, *infix*).\n" ++
245 " When asked to modify a database (register, unregister, update,\n"++
246 " hide, expose, and also check), ghc-pkg modifies the global database by\n"++
247 " default. Specifying --user causes it to act on the user database,\n"++
248 " or --package-conf can be used to act on another database\n"++
249 " entirely. When multiple of these options are given, the rightmost\n"++
250 " one is used as the database to act upon.\n"++
252 " Commands that query the package database (list, tree, latest, describe,\n"++
253 " field) operate on the list of databases specified by the flags\n"++
254 " --user, --global, and --package-conf. If none of these flags are\n"++
255 " given, the default is --global --user.\n"++
257 " The following optional flags are also accepted:\n"
259 substProg :: String -> String -> String
261 substProg prog ('$':'p':xs) = prog ++ substProg prog xs
262 substProg prog (c:xs) = c : substProg prog xs
264 -- -----------------------------------------------------------------------------
267 data Force = NoForce | ForceFiles | ForceAll | CannotForce
270 data PackageArg = Id PackageIdentifier | Substring String (String->Bool)
272 runit :: Verbosity -> [Flag] -> [String] -> IO ()
273 runit verbosity cli nonopts = do
274 installSignalHandlers -- catch ^C and clean up
275 prog <- getProgramName
278 | FlagForce `elem` cli = ForceAll
279 | FlagForceFiles `elem` cli = ForceFiles
280 | otherwise = NoForce
281 auto_ghci_libs = FlagAutoGHCiLibs `elem` cli
282 splitFields fields = unfoldr splitComma (',':fields)
283 where splitComma "" = Nothing
284 splitComma fs = Just $ break (==',') (tail fs)
286 substringCheck :: String -> Maybe (String -> Bool)
287 substringCheck "" = Nothing
288 substringCheck "*" = Just (const True)
289 substringCheck [_] = Nothing
290 substringCheck (h:t) =
291 case (h, init t, last t) of
292 ('*',s,'*') -> Just (isInfixOf (f s) . f)
293 ('*',_, _ ) -> Just (isSuffixOf (f t) . f)
294 ( _ ,s,'*') -> Just (isPrefixOf (f (h:s)) . f)
296 where f | FlagIgnoreCase `elem` cli = map toLower
299 glob x | System.Info.os=="mingw32" = do
300 -- glob echoes its argument, after win32 filename globbing
301 (_,o,_,_) <- runInteractiveCommand ("glob "++x)
302 txt <- hGetContents o
304 glob x | otherwise = return [x]
307 -- first, parse the command
310 -- dummy command to demonstrate usage and permit testing
311 -- without messing things up; use glob to selectively enable
312 -- windows filename globbing for file parameters
313 -- register, update, FlagGlobalConfig, FlagConfig; others?
314 ["glob", filename] -> do
316 glob filename >>= print
318 ["init", filename] ->
319 initPackageDB filename verbosity cli
320 ["register", filename] ->
321 registerPackage filename verbosity cli auto_ghci_libs False force
322 ["update", filename] ->
323 registerPackage filename verbosity cli auto_ghci_libs True force
324 ["unregister", pkgid_str] -> do
325 pkgid <- readGlobPkgId pkgid_str
326 unregisterPackage pkgid verbosity cli force
327 ["expose", pkgid_str] -> do
328 pkgid <- readGlobPkgId pkgid_str
329 exposePackage pkgid verbosity cli force
330 ["hide", pkgid_str] -> do
331 pkgid <- readGlobPkgId pkgid_str
332 hidePackage pkgid verbosity cli force
334 listPackages verbosity cli Nothing Nothing
335 ["list", pkgid_str] ->
336 case substringCheck pkgid_str of
337 Nothing -> do pkgid <- readGlobPkgId pkgid_str
338 listPackages verbosity cli (Just (Id pkgid)) Nothing
339 Just m -> listPackages verbosity cli (Just (Substring pkgid_str m)) Nothing
341 showPackageDot verbosity cli
342 ["find-module", moduleName] -> do
343 let match = maybe (==moduleName) id (substringCheck moduleName)
344 listPackages verbosity cli Nothing (Just match)
345 ["latest", pkgid_str] -> do
346 pkgid <- readGlobPkgId pkgid_str
347 latestPackage verbosity cli pkgid
348 ["describe", pkgid_str] ->
349 case substringCheck pkgid_str of
350 Nothing -> do pkgid <- readGlobPkgId pkgid_str
351 describePackage verbosity cli (Id pkgid)
352 Just m -> describePackage verbosity cli (Substring pkgid_str m)
353 ["field", pkgid_str, fields] ->
354 case substringCheck pkgid_str of
355 Nothing -> do pkgid <- readGlobPkgId pkgid_str
356 describeField verbosity cli (Id pkgid)
358 Just m -> describeField verbosity cli (Substring pkgid_str m)
361 checkConsistency verbosity cli
364 dumpPackages verbosity cli
367 recache verbosity cli
370 die ("missing command\n" ++
371 usageInfo (usageHeader prog) flags)
373 die ("command-line syntax error\n" ++
374 usageInfo (usageHeader prog) flags)
376 parseCheck :: ReadP a a -> String -> String -> IO a
377 parseCheck parser str what =
378 case [ x | (x,ys) <- readP_to_S parser str, all isSpace ys ] of
380 _ -> die ("cannot parse \'" ++ str ++ "\' as a " ++ what)
382 readGlobPkgId :: String -> IO PackageIdentifier
383 readGlobPkgId str = parseCheck parseGlobPackageId str "package identifier"
385 parseGlobPackageId :: ReadP r PackageIdentifier
391 return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion }))
393 -- globVersion means "all versions"
394 globVersion :: Version
395 globVersion = Version{ versionBranch=[], versionTags=["*"] }
397 -- -----------------------------------------------------------------------------
400 -- Some commands operate on a single database:
401 -- register, unregister, expose, hide
402 -- however these commands also check the union of the available databases
403 -- in order to check consistency. For example, register will check that
404 -- dependencies exist before registering a package.
406 -- Some commands operate on multiple databases, with overlapping semantics:
407 -- list, describe, field
410 = PackageDB { location :: FilePath,
411 packages :: [InstalledPackageInfo] }
413 type PackageDBStack = [PackageDB]
414 -- A stack of package databases. Convention: head is the topmost
417 allPackagesInStack :: PackageDBStack -> [InstalledPackageInfo]
418 allPackagesInStack = concatMap packages
420 getPkgDatabases :: Verbosity
421 -> Bool -- we are modifying, not reading
422 -> Bool -- read caches, if available
424 -> IO (PackageDBStack,
425 -- the real package DB stack: [global,user] ++
426 -- DBs specified on the command line with -f.
428 -- which one to modify, if any
430 -- the package DBs specified on the command
431 -- line, or [global,user] otherwise. This
432 -- is used as the list of package DBs for
433 -- commands that just read the DB, such as 'list'.
435 getPkgDatabases verbosity modify use_cache my_flags = do
436 -- first we determine the location of the global package config. On Windows,
437 -- this is found relative to the ghc-pkg.exe binary, whereas on Unix the
438 -- location is passed to the binary using the --global-config flag by the
440 let err_msg = "missing --global-conf option, location of global package.conf unknown\n"
442 case [ f | FlagGlobalConfig f <- my_flags ] of
443 [] -> do mb_dir <- getLibDir
445 Nothing -> die err_msg
447 r <- lookForPackageDBIn dir
449 Nothing -> die ("Can't find package database in " ++ dir)
450 Just path -> return path
451 fs -> return (last fs)
453 let no_user_db = FlagNoUserDb `elem` my_flags
455 -- get the location of the user package database, and create it if necessary
456 -- getAppUserDataDirectory can fail (e.g. if $HOME isn't set)
457 e_appdir <- try $ getAppUserDataDirectory "ghc"
460 if no_user_db then return Nothing else
462 Left _ -> return Nothing
464 let subdir = targetARCH ++ '-':targetOS ++ '-':Version.version
465 dir = appdir </> subdir
466 r <- lookForPackageDBIn dir
468 Nothing -> return (Just (dir </> "package.conf.d", False))
469 Just f -> return (Just (f, True))
471 -- If the user database doesn't exist, and this command isn't a
472 -- "modify" command, then we won't attempt to create or use it.
474 | Just (user_conf,user_exists) <- mb_user_conf,
475 modify || user_exists = [user_conf, global_conf]
476 | otherwise = [global_conf]
478 e_pkg_path <- try (System.Environment.getEnv "GHC_PACKAGE_PATH")
481 Left _ -> sys_databases
483 | last cs == "" -> init cs ++ sys_databases
485 where cs = parseSearchPath path
487 -- The "global" database is always the one at the bottom of the stack.
488 -- This is the database we modify by default.
489 virt_global_conf = last env_stack
491 let db_flags = [ f | Just f <- map is_db_flag my_flags ]
492 where is_db_flag FlagUser
493 | Just (user_conf, _user_exists) <- mb_user_conf
495 is_db_flag FlagGlobal = Just virt_global_conf
496 is_db_flag (FlagConfig f) = Just f
497 is_db_flag _ = Nothing
499 let flag_db_names | null db_flags = env_stack
500 | otherwise = reverse (nub db_flags)
502 -- For a "modify" command, treat all the databases as
503 -- a stack, where we are modifying the top one, but it
504 -- can refer to packages in databases further down the
507 -- -f flags on the command line add to the database
508 -- stack, unless any of them are present in the stack
510 let final_stack = filter (`notElem` env_stack)
511 [ f | FlagConfig f <- reverse my_flags ]
514 -- the database we actually modify is the one mentioned
515 -- rightmost on the command-line.
517 | not modify = Nothing
518 | null db_flags = Just virt_global_conf
519 | otherwise = Just (last db_flags)
521 db_stack <- mapM (readParseDatabase verbosity mb_user_conf use_cache) final_stack
523 let flag_db_stack = [ db | db_name <- flag_db_names,
524 db <- db_stack, location db == db_name ]
526 return (db_stack, to_modify, flag_db_stack)
529 lookForPackageDBIn :: FilePath -> IO (Maybe FilePath)
530 lookForPackageDBIn dir = do
531 let path_dir = dir </> "package.conf.d"
532 exists_dir <- doesDirectoryExist path_dir
533 if exists_dir then return (Just path_dir) else do
534 let path_file = dir </> "package.conf"
535 exists_file <- doesFileExist path_file
536 if exists_file then return (Just path_file) else return Nothing
538 readParseDatabase :: Verbosity
539 -> Maybe (FilePath,Bool)
544 readParseDatabase verbosity mb_user_conf use_cache path
545 -- the user database (only) is allowed to be non-existent
546 | Just (user_conf,False) <- mb_user_conf, path == user_conf
547 = return PackageDB { location = path, packages = [] }
549 = do e <- try $ getDirectoryContents path
552 pkgs <- parseMultiPackageConf verbosity path
553 return PackageDB{ location = path, packages = pkgs }
555 | not use_cache -> ignore_cache
557 let cache = path </> cachefilename
558 tdir <- getModificationTime path
559 e_tcache <- try $ getModificationTime cache
562 when (verbosity > Normal) $
563 warn ("warning: cannot read cache file " ++ cache ++ ": " ++ show ex)
566 | tcache >= tdir -> do
567 when (verbosity > Normal) $
568 putStrLn ("using cache: " ++ cache)
569 pkgs <- myReadBinPackageDB cache
570 let pkgs' = map convertPackageInfoIn pkgs
571 return PackageDB { location = path, packages = pkgs' }
573 when (verbosity >= Normal) $ do
574 warn ("WARNING: cache is out of date: " ++ cache)
575 warn " use 'ghc-pkg recache' to fix."
579 let confs = filter (".conf" `isSuffixOf`) fs
580 pkgs <- mapM (parseSingletonPackageConf verbosity) $
582 return PackageDB { location = path, packages = pkgs }
584 -- read the package.cache file strictly, to work around a problem with
585 -- bytestring 0.9.0.x (fixed in 0.9.1.x) where the file wasn't closed
586 -- after it has been completely read, leading to a sharing violation
588 myReadBinPackageDB :: FilePath -> IO [InstalledPackageInfoString]
589 myReadBinPackageDB filepath = do
590 h <- openBinaryFile filepath ReadMode
592 b <- B.hGet h (fromIntegral sz)
594 return $ Bin.runGet Bin.get b
596 parseMultiPackageConf :: Verbosity -> FilePath -> IO [InstalledPackageInfo]
597 parseMultiPackageConf verbosity file = do
598 when (verbosity > Normal) $ putStrLn ("reading package database: " ++ file)
599 str <- readUTF8File file
600 let pkgs = map convertPackageInfoIn $ read str
601 Exception.evaluate pkgs
603 die ("error while parsing " ++ file ++ ": " ++ show e)
605 parseSingletonPackageConf :: Verbosity -> FilePath -> IO InstalledPackageInfo
606 parseSingletonPackageConf verbosity file = do
607 when (verbosity > Normal) $ putStrLn ("reading package config: " ++ file)
608 readUTF8File file >>= parsePackageInfo
610 cachefilename :: FilePath
611 cachefilename = "package.cache"
613 -- -----------------------------------------------------------------------------
614 -- Creating a new package DB
616 initPackageDB :: FilePath -> Verbosity -> [Flag] -> IO ()
617 initPackageDB filename verbosity _flags = do
618 let eexist = die ("cannot create: " ++ filename ++ " already exists")
619 b1 <- doesFileExist filename
621 b2 <- doesDirectoryExist filename
623 changeDB verbosity [] PackageDB{ location = filename, packages = [] }
625 -- -----------------------------------------------------------------------------
628 registerPackage :: FilePath
631 -> Bool -- auto_ghci_libs
635 registerPackage input verbosity my_flags auto_ghci_libs update force = do
636 (db_stack, Just to_modify, _flag_dbs) <-
637 getPkgDatabases verbosity True True my_flags
640 db_to_operate_on = my_head "register" $
641 filter ((== to_modify).location) db_stack
646 when (verbosity >= Normal) $
647 putStr "Reading package info from stdin ... "
648 #if __GLASGOW_HASKELL__ >= 612
649 -- fix the encoding to UTF-8, since this is an interchange format
650 hSetEncoding stdin utf8
654 when (verbosity >= Normal) $
655 putStr ("Reading package info from " ++ show f ++ " ... ")
658 expanded <- expandEnvVars s force
660 pkg <- parsePackageInfo expanded
661 when (verbosity >= Normal) $
664 let truncated_stack = dropWhile ((/= to_modify).location) db_stack
665 -- truncate the stack for validation, because we don't allow
666 -- packages lower in the stack to refer to those higher up.
667 validatePackageConfig pkg truncated_stack auto_ghci_libs update force
669 removes = [ RemovePackage p
670 | p <- packages db_to_operate_on,
671 sourcePackageId p == sourcePackageId pkg ]
673 changeDB verbosity (removes ++ [AddPackage pkg]) db_to_operate_on
677 -> IO InstalledPackageInfo
678 parsePackageInfo str =
679 case parseInstalledPackageInfo str of
680 ParseOk _warns ok -> return ok
681 ParseFailed err -> case locatedErrorMsg err of
682 (Nothing, s) -> die s
683 (Just l, s) -> die (show l ++ ": " ++ s)
685 -- -----------------------------------------------------------------------------
686 -- Making changes to a package database
688 data DBOp = RemovePackage InstalledPackageInfo
689 | AddPackage InstalledPackageInfo
690 | ModifyPackage InstalledPackageInfo
692 changeDB :: Verbosity -> [DBOp] -> PackageDB -> IO ()
693 changeDB verbosity cmds db = do
694 let db' = updateInternalDB db cmds
695 isfile <- doesFileExist (location db)
697 then writeNewConfig verbosity (location db') (packages db')
699 createDirectoryIfMissing True (location db)
700 changeDBDir verbosity cmds db'
702 updateInternalDB :: PackageDB -> [DBOp] -> PackageDB
703 updateInternalDB db cmds = db{ packages = foldl do_cmd (packages db) cmds }
705 do_cmd pkgs (RemovePackage p) =
706 filter ((/= installedPackageId p) . installedPackageId) pkgs
707 do_cmd pkgs (AddPackage p) = p : pkgs
708 do_cmd pkgs (ModifyPackage p) =
709 do_cmd (do_cmd pkgs (RemovePackage p)) (AddPackage p)
712 changeDBDir :: Verbosity -> [DBOp] -> PackageDB -> IO ()
713 changeDBDir verbosity cmds db = do
715 updateDBCache verbosity db
717 do_cmd (RemovePackage p) = do
718 let file = location db </> display (installedPackageId p) <.> "conf"
719 when (verbosity > Normal) $ putStrLn ("removing " ++ file)
721 do_cmd (AddPackage p) = do
722 let file = location db </> display (installedPackageId p) <.> "conf"
723 when (verbosity > Normal) $ putStrLn ("writing " ++ file)
724 writeFileUtf8Atomic file (showInstalledPackageInfo p)
725 do_cmd (ModifyPackage p) =
726 do_cmd (AddPackage p)
728 updateDBCache :: Verbosity -> PackageDB -> IO ()
729 updateDBCache verbosity db = do
730 let filename = location db </> cachefilename
731 when (verbosity > Normal) $
732 putStrLn ("writing cache " ++ filename)
733 writeBinaryFileAtomic filename (map convertPackageInfoOut (packages db))
735 if isPermissionError e
736 then die (filename ++ ": you don't have permission to modify this file")
739 -- -----------------------------------------------------------------------------
740 -- Exposing, Hiding, Unregistering are all similar
742 exposePackage :: PackageIdentifier -> Verbosity -> [Flag] -> Force -> IO ()
743 exposePackage = modifyPackage (\p -> ModifyPackage p{exposed=True})
745 hidePackage :: PackageIdentifier -> Verbosity -> [Flag] -> Force -> IO ()
746 hidePackage = modifyPackage (\p -> ModifyPackage p{exposed=False})
748 unregisterPackage :: PackageIdentifier -> Verbosity -> [Flag] -> Force -> IO ()
749 unregisterPackage = modifyPackage RemovePackage
752 :: (InstalledPackageInfo -> DBOp)
758 modifyPackage fn pkgid verbosity my_flags force = do
759 (db_stack, Just _to_modify, _flag_dbs) <-
760 getPkgDatabases verbosity True{-modify-} True{-use cache-} my_flags
762 (db, ps) <- fmap head $ findPackagesByDB db_stack (Id pkgid)
764 db_name = location db
767 pids = map sourcePackageId ps
769 cmds = [ fn pkg | pkg <- pkgs, sourcePackageId pkg `elem` pids ]
770 new_db = updateInternalDB db cmds
772 old_broken = brokenPackages (allPackagesInStack db_stack)
773 rest_of_stack = filter ((/= db_name) . location) db_stack
774 new_stack = new_db : rest_of_stack
775 new_broken = map sourcePackageId (brokenPackages (allPackagesInStack new_stack))
776 newly_broken = filter (`notElem` map sourcePackageId old_broken) new_broken
778 when (not (null newly_broken)) $
779 dieOrForceAll force ("unregistering " ++ display pkgid ++
780 " would break the following packages: "
781 ++ unwords (map display newly_broken))
783 changeDB verbosity cmds db
785 recache :: Verbosity -> [Flag] -> IO ()
786 recache verbosity my_flags = do
787 (db_stack, Just to_modify, _flag_dbs) <-
788 getPkgDatabases verbosity True{-modify-} False{-no cache-} my_flags
790 db_to_operate_on = my_head "recache" $
791 filter ((== to_modify).location) db_stack
793 changeDB verbosity [] db_to_operate_on
795 -- -----------------------------------------------------------------------------
798 listPackages :: Verbosity -> [Flag] -> Maybe PackageArg
799 -> Maybe (String->Bool)
801 listPackages verbosity my_flags mPackageName mModuleName = do
802 let simple_output = FlagSimpleOutput `elem` my_flags
803 (db_stack, _, flag_db_stack) <-
804 getPkgDatabases verbosity False True{-use cache-} my_flags
806 let db_stack_filtered -- if a package is given, filter out all other packages
807 | Just this <- mPackageName =
808 [ db{ packages = filter (this `matchesPkg`) (packages db) }
809 | db <- flag_db_stack ]
810 | Just match <- mModuleName = -- packages which expose mModuleName
811 [ db{ packages = filter (match `exposedInPkg`) (packages db) }
812 | db <- flag_db_stack ]
813 | otherwise = flag_db_stack
816 = [ db{ packages = sort_pkgs (packages db) }
817 | db <- db_stack_filtered ]
818 where sort_pkgs = sortBy cmpPkgIds
819 cmpPkgIds pkg1 pkg2 =
820 case pkgName p1 `compare` pkgName p2 of
823 EQ -> pkgVersion p1 `compare` pkgVersion p2
824 where (p1,p2) = (sourcePackageId pkg1, sourcePackageId pkg2)
826 stack = reverse db_stack_sorted
828 match `exposedInPkg` pkg = any match (map display $ exposedModules pkg)
830 pkg_map = allPackagesInStack db_stack
831 broken = map sourcePackageId (brokenPackages pkg_map)
833 show_normal PackageDB{ location = db_name, packages = pkg_confs } =
834 hPutStrLn stdout $ unlines ((db_name ++ ":") : map (" " ++) pp_pkgs)
836 pp_pkgs = map pp_pkg pkg_confs
838 | sourcePackageId p `elem` broken = printf "{%s}" doc
840 | otherwise = printf "(%s)" doc
841 where doc | verbosity >= Verbose = printf "%s (%s)" pkg ipid
844 InstalledPackageId ipid = installedPackageId p
845 pkg = display (sourcePackageId p)
847 show_simple = simplePackageList my_flags . allPackagesInStack
849 when (not (null broken) && not simple_output && verbosity /= Silent) $ do
850 prog <- getProgramName
851 warn ("WARNING: there are broken packages. Run '" ++ prog ++ " check' for more details.")
853 if simple_output then show_simple stack else do
855 #if defined(mingw32_HOST_OS) || __GLASGOW_HASKELL__ < 611 || defined(BOOTSTRAPPING)
856 mapM_ show_normal stack
859 show_colour withF db =
860 mconcat $ map (<#> termText "\n") $
861 (termText (location db) :
862 map (termText " " <#>) (map pp_pkg (packages db)))
865 | sourcePackageId p `elem` broken = withF Red doc
867 | otherwise = withF Blue doc
868 where doc | verbosity >= Verbose
869 = termText (printf "%s (%s)" pkg ipid)
873 InstalledPackageId ipid = installedPackageId p
874 pkg = display (sourcePackageId p)
876 is_tty <- hIsTerminalDevice stdout
878 then mapM_ show_normal stack
879 else do tty <- Terminfo.setupTermFromEnv
880 case Terminfo.getCapability tty withForegroundColor of
881 Nothing -> mapM_ show_normal stack
882 Just w -> runTermOutput tty $ mconcat $
883 map (show_colour w) stack
886 simplePackageList :: [Flag] -> [InstalledPackageInfo] -> IO ()
887 simplePackageList my_flags pkgs = do
888 let showPkg = if FlagNamesOnly `elem` my_flags then display . pkgName
890 strs = map showPkg $ sortBy compPkgIdVer $ map sourcePackageId pkgs
891 when (not (null pkgs)) $
892 hPutStrLn stdout $ concat $ intersperse " " strs
894 showPackageDot :: Verbosity -> [Flag] -> IO ()
895 showPackageDot verbosity myflags = do
896 (_, _, flag_db_stack) <-
897 getPkgDatabases verbosity False True{-use cache-} myflags
899 let all_pkgs = allPackagesInStack flag_db_stack
900 ipix = PackageIndex.fromList all_pkgs
903 let quote s = '"':s ++ "\""
904 mapM_ putStrLn [ quote from ++ " -> " ++ quote to
906 let from = display (sourcePackageId p),
908 Just dep <- [PackageIndex.lookupInstalledPackageId ipix depid],
909 let to = display (sourcePackageId dep)
913 -- -----------------------------------------------------------------------------
914 -- Prints the highest (hidden or exposed) version of a package
916 latestPackage :: Verbosity -> [Flag] -> PackageIdentifier -> IO ()
917 latestPackage verbosity my_flags pkgid = do
918 (_, _, flag_db_stack) <-
919 getPkgDatabases verbosity False True{-use cache-} my_flags
921 ps <- findPackages flag_db_stack (Id pkgid)
922 show_pkg (sortBy compPkgIdVer (map sourcePackageId ps))
924 show_pkg [] = die "no matches"
925 show_pkg pids = hPutStrLn stdout (display (last pids))
927 -- -----------------------------------------------------------------------------
930 describePackage :: Verbosity -> [Flag] -> PackageArg -> IO ()
931 describePackage verbosity my_flags pkgarg = do
932 (_, _, flag_db_stack) <-
933 getPkgDatabases verbosity False True{-use cache-} my_flags
934 ps <- findPackages flag_db_stack pkgarg
937 dumpPackages :: Verbosity -> [Flag] -> IO ()
938 dumpPackages verbosity my_flags = do
939 (_, _, flag_db_stack) <-
940 getPkgDatabases verbosity False True{-use cache-} my_flags
941 doDump (allPackagesInStack flag_db_stack)
943 doDump :: [InstalledPackageInfo] -> IO ()
945 #if __GLASGOW_HASKELL__ >= 612
946 -- fix the encoding to UTF-8, since this is an interchange format
947 hSetEncoding stdout utf8
949 mapM_ putStrLn . intersperse "---" . map showInstalledPackageInfo $ pkgs
951 -- PackageId is can have globVersion for the version
952 findPackages :: PackageDBStack -> PackageArg -> IO [InstalledPackageInfo]
953 findPackages db_stack pkgarg
954 = fmap (concatMap snd) $ findPackagesByDB db_stack pkgarg
956 findPackagesByDB :: PackageDBStack -> PackageArg
957 -> IO [(PackageDB, [InstalledPackageInfo])]
958 findPackagesByDB db_stack pkgarg
959 = case [ (db, matched)
961 let matched = filter (pkgarg `matchesPkg`) (packages db),
962 not (null matched) ] of
963 [] -> die ("cannot find package " ++ pkg_msg pkgarg)
966 pkg_msg (Id pkgid) = display pkgid
967 pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat
969 matches :: PackageIdentifier -> PackageIdentifier -> Bool
971 = (pkgName pid == pkgName pid')
972 && (pkgVersion pid == pkgVersion pid' || not (realVersion pid))
974 realVersion :: PackageIdentifier -> Bool
975 realVersion pkgid = versionBranch (pkgVersion pkgid) /= []
976 -- when versionBranch == [], this is a glob
978 matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool
979 (Id pid) `matchesPkg` pkg = pid `matches` sourcePackageId pkg
980 (Substring _ m) `matchesPkg` pkg = m (display (sourcePackageId pkg))
982 compPkgIdVer :: PackageIdentifier -> PackageIdentifier -> Ordering
983 compPkgIdVer p1 p2 = pkgVersion p1 `compare` pkgVersion p2
985 -- -----------------------------------------------------------------------------
988 describeField :: Verbosity -> [Flag] -> PackageArg -> [String] -> IO ()
989 describeField verbosity my_flags pkgarg fields = do
990 (_, _, flag_db_stack) <-
991 getPkgDatabases verbosity False True{-use cache-} my_flags
992 fns <- toFields fields
993 ps <- findPackages flag_db_stack pkgarg
994 let top_dir = takeDirectory (location (last flag_db_stack))
995 mapM_ (selectFields fns) (mungePackagePaths top_dir ps)
996 where toFields [] = return []
997 toFields (f:fs) = case toField f of
998 Nothing -> die ("unknown field: " ++ f)
999 Just fn -> do fns <- toFields fs
1001 selectFields fns info = mapM_ (\fn->putStrLn (fn info)) fns
1003 mungePackagePaths :: String -> [InstalledPackageInfo] -> [InstalledPackageInfo]
1004 -- Replace the strings "$topdir" and "$httptopdir" at the beginning of a path
1005 -- with the current topdir (obtained from the -B option).
1006 mungePackagePaths top_dir ps = map munge_pkg ps
1008 munge_pkg p = p{ importDirs = munge_paths (importDirs p),
1009 includeDirs = munge_paths (includeDirs p),
1010 libraryDirs = munge_paths (libraryDirs p),
1011 frameworkDirs = munge_paths (frameworkDirs p),
1012 haddockInterfaces = munge_paths (haddockInterfaces p),
1013 haddockHTMLs = munge_paths (haddockHTMLs p)
1016 munge_paths = map munge_path
1019 | Just p' <- maybePrefixMatch "$topdir" p = top_dir ++ p'
1020 | Just p' <- maybePrefixMatch "$httptopdir" p = toHttpPath top_dir ++ p'
1023 toHttpPath p = "file:///" ++ p
1025 maybePrefixMatch :: String -> String -> Maybe String
1026 maybePrefixMatch [] rest = Just rest
1027 maybePrefixMatch (_:_) [] = Nothing
1028 maybePrefixMatch (p:pat) (r:rest)
1029 | p == r = maybePrefixMatch pat rest
1030 | otherwise = Nothing
1032 toField :: String -> Maybe (InstalledPackageInfo -> String)
1033 -- backwards compatibility:
1034 toField "import_dirs" = Just $ strList . importDirs
1035 toField "source_dirs" = Just $ strList . importDirs
1036 toField "library_dirs" = Just $ strList . libraryDirs
1037 toField "hs_libraries" = Just $ strList . hsLibraries
1038 toField "extra_libraries" = Just $ strList . extraLibraries
1039 toField "include_dirs" = Just $ strList . includeDirs
1040 toField "c_includes" = Just $ strList . includes
1041 toField "package_deps" = Just $ strList . map display. depends
1042 toField "extra_cc_opts" = Just $ strList . ccOptions
1043 toField "extra_ld_opts" = Just $ strList . ldOptions
1044 toField "framework_dirs" = Just $ strList . frameworkDirs
1045 toField "extra_frameworks"= Just $ strList . frameworks
1046 toField s = showInstalledPackageInfoField s
1048 strList :: [String] -> String
1052 -- -----------------------------------------------------------------------------
1053 -- Check: Check consistency of installed packages
1055 checkConsistency :: Verbosity -> [Flag] -> IO ()
1056 checkConsistency verbosity my_flags = do
1057 (db_stack, _, _) <- getPkgDatabases verbosity True True{-use cache-} my_flags
1058 -- check behaves like modify for the purposes of deciding which
1059 -- databases to use, because ordering is important.
1061 let simple_output = FlagSimpleOutput `elem` my_flags
1063 let pkgs = allPackagesInStack db_stack
1066 (_,es,ws) <- runValidate $ checkPackageConfig p db_stack False True
1068 then do when (not simple_output) $ do
1069 _ <- reportValidateErrors [] ws "" Nothing
1073 when (not simple_output) $ do
1074 reportError ("There are problems in package " ++ display (sourcePackageId p) ++ ":")
1075 _ <- reportValidateErrors es ws " " Nothing
1079 broken_pkgs <- concat `fmap` mapM checkPackage pkgs
1081 let filterOut pkgs1 pkgs2 = filter not_in pkgs2
1082 where not_in p = sourcePackageId p `notElem` all_ps
1083 all_ps = map sourcePackageId pkgs1
1085 let not_broken_pkgs = filterOut broken_pkgs pkgs
1086 (_, trans_broken_pkgs) = closure [] not_broken_pkgs
1087 all_broken_pkgs = broken_pkgs ++ trans_broken_pkgs
1089 when (not (null all_broken_pkgs)) $ do
1091 then simplePackageList my_flags all_broken_pkgs
1093 reportError ("\nThe following packages are broken, either because they have a problem\n"++
1094 "listed above, or because they depend on a broken package.")
1095 mapM_ (hPutStrLn stderr . display . sourcePackageId) all_broken_pkgs
1097 when (not (null all_broken_pkgs)) $ exitWith (ExitFailure 1)
1100 closure :: [InstalledPackageInfo] -> [InstalledPackageInfo]
1101 -> ([InstalledPackageInfo], [InstalledPackageInfo])
1102 closure pkgs db_stack = go pkgs db_stack
1104 go avail not_avail =
1105 case partition (depsAvailable avail) not_avail of
1106 ([], not_avail') -> (avail, not_avail')
1107 (new_avail, not_avail') -> go (new_avail ++ avail) not_avail'
1109 depsAvailable :: [InstalledPackageInfo] -> InstalledPackageInfo
1111 depsAvailable pkgs_ok pkg = null dangling
1112 where dangling = filter (`notElem` pids) (depends pkg)
1113 pids = map installedPackageId pkgs_ok
1115 -- we want mutually recursive groups of package to show up
1116 -- as broken. (#1750)
1118 brokenPackages :: [InstalledPackageInfo] -> [InstalledPackageInfo]
1119 brokenPackages pkgs = snd (closure [] pkgs)
1121 -- -----------------------------------------------------------------------------
1122 -- Manipulating package.conf files
1124 type InstalledPackageInfoString = InstalledPackageInfo_ String
1126 convertPackageInfoOut :: InstalledPackageInfo -> InstalledPackageInfoString
1127 convertPackageInfoOut
1128 (pkgconf@(InstalledPackageInfo { exposedModules = e,
1129 hiddenModules = h })) =
1130 pkgconf{ exposedModules = map display e,
1131 hiddenModules = map display h }
1133 convertPackageInfoIn :: InstalledPackageInfoString -> InstalledPackageInfo
1134 convertPackageInfoIn
1135 (pkgconf@(InstalledPackageInfo { exposedModules = e,
1136 hiddenModules = h })) =
1137 pkgconf{ exposedModules = map convert e,
1138 hiddenModules = map convert h }
1139 where convert = fromJust . simpleParse
1141 writeNewConfig :: Verbosity -> FilePath -> [InstalledPackageInfo] -> IO ()
1142 writeNewConfig verbosity filename ipis = do
1143 when (verbosity >= Normal) $
1144 hPutStr stdout "Writing new package config file... "
1145 createDirectoryIfMissing True $ takeDirectory filename
1146 let shown = concat $ intersperse ",\n "
1147 $ map (show . convertPackageInfoOut) ipis
1148 fileContents = "[" ++ shown ++ "\n]"
1149 writeFileUtf8Atomic filename fileContents
1151 if isPermissionError e
1152 then die (filename ++ ": you don't have permission to modify this file")
1154 when (verbosity >= Normal) $
1155 hPutStrLn stdout "done."
1157 -----------------------------------------------------------------------------
1158 -- Sanity-check a new package config, and automatically build GHCi libs
1161 type ValidateError = (Force,String)
1162 type ValidateWarning = String
1164 newtype Validate a = V { runValidate :: IO (a, [ValidateError],[ValidateWarning]) }
1166 instance Monad Validate where
1167 return a = V $ return (a, [], [])
1169 (a, es, ws) <- runValidate m
1170 (b, es', ws') <- runValidate (k a)
1171 return (b,es++es',ws++ws')
1173 verror :: Force -> String -> Validate ()
1174 verror f s = V (return ((),[(f,s)],[]))
1176 vwarn :: String -> Validate ()
1177 vwarn s = V (return ((),[],["Warning: " ++ s]))
1179 liftIO :: IO a -> Validate a
1180 liftIO k = V (k >>= \a -> return (a,[],[]))
1182 -- returns False if we should die
1183 reportValidateErrors :: [ValidateError] -> [ValidateWarning]
1184 -> String -> Maybe Force -> IO Bool
1185 reportValidateErrors es ws prefix mb_force = do
1186 mapM_ (warn . (prefix++)) ws
1187 oks <- mapM report es
1191 | Just force <- mb_force
1193 then do reportError (prefix ++ s ++ " (ignoring)")
1195 else if f < CannotForce
1196 then do reportError (prefix ++ s ++ " (use --force to override)")
1198 else do reportError err
1200 | otherwise = do reportError err
1205 validatePackageConfig :: InstalledPackageInfo
1207 -> Bool -- auto-ghc-libs
1208 -> Bool -- update, or check
1211 validatePackageConfig pkg db_stack auto_ghci_libs update force = do
1212 (_,es,ws) <- runValidate $ checkPackageConfig pkg db_stack auto_ghci_libs update
1213 ok <- reportValidateErrors es ws (display (sourcePackageId pkg) ++ ": ") (Just force)
1214 when (not ok) $ exitWith (ExitFailure 1)
1216 checkPackageConfig :: InstalledPackageInfo
1218 -> Bool -- auto-ghc-libs
1219 -> Bool -- update, or check
1221 checkPackageConfig pkg db_stack auto_ghci_libs update = do
1222 checkInstalledPackageId pkg db_stack update
1224 checkDuplicates db_stack pkg update
1225 mapM_ (checkDep db_stack) (depends pkg)
1226 checkDuplicateDepends (depends pkg)
1227 mapM_ (checkDir False "import-dirs") (importDirs pkg)
1228 mapM_ (checkDir True "library-dirs") (libraryDirs pkg)
1229 mapM_ (checkDir True "include-dirs") (includeDirs pkg)
1231 mapM_ (checkHSLib (libraryDirs pkg) auto_ghci_libs) (hsLibraries pkg)
1232 -- ToDo: check these somehow?
1233 -- extra_libraries :: [String],
1234 -- c_includes :: [String],
1236 checkInstalledPackageId :: InstalledPackageInfo -> PackageDBStack -> Bool
1238 checkInstalledPackageId ipi db_stack update = do
1239 let ipid@(InstalledPackageId str) = installedPackageId ipi
1240 when (null str) $ verror CannotForce "missing id field"
1241 let dups = [ p | p <- allPackagesInStack db_stack,
1242 installedPackageId p == ipid ]
1243 when (not update && not (null dups)) $
1244 verror CannotForce $
1245 "package(s) with this id already exist: " ++
1246 unwords (map (display.packageId) dups)
1248 -- When the package name and version are put together, sometimes we can
1249 -- end up with a package id that cannot be parsed. This will lead to
1250 -- difficulties when the user wants to refer to the package later, so
1251 -- we check that the package id can be parsed properly here.
1252 checkPackageId :: InstalledPackageInfo -> Validate ()
1253 checkPackageId ipi =
1254 let str = display (sourcePackageId ipi) in
1255 case [ x :: PackageIdentifier | (x,ys) <- readP_to_S parse str, all isSpace ys ] of
1257 [] -> verror CannotForce ("invalid package identifier: " ++ str)
1258 _ -> verror CannotForce ("ambiguous package identifier: " ++ str)
1260 checkDuplicates :: PackageDBStack -> InstalledPackageInfo -> Bool -> Validate ()
1261 checkDuplicates db_stack pkg update = do
1263 pkgid = sourcePackageId pkg
1264 pkgs = packages (head db_stack)
1266 -- Check whether this package id already exists in this DB
1268 when (not update && (pkgid `elem` map sourcePackageId pkgs)) $
1269 verror CannotForce $
1270 "package " ++ display pkgid ++ " is already installed"
1273 uncasep = map toLower . display
1274 dups = filter ((== uncasep pkgid) . uncasep) (map sourcePackageId pkgs)
1276 when (not update && not (null dups)) $ verror ForceAll $
1277 "Package names may be treated case-insensitively in the future.\n"++
1278 "Package " ++ display pkgid ++
1279 " overlaps with: " ++ unwords (map display dups)
1282 checkDir :: Bool -> String -> String -> Validate ()
1283 checkDir warn_only thisfield d
1284 | "$topdir" `isPrefixOf` d = return ()
1285 | "$httptopdir" `isPrefixOf` d = return ()
1286 -- can't check these, because we don't know what $(http)topdir is
1287 | isRelative d = verror ForceFiles $
1288 thisfield ++ ": " ++ d ++ " is a relative path"
1289 -- relative paths don't make any sense; #4134
1291 there <- liftIO $ doesDirectoryExist d
1293 let msg = thisfield ++ ": " ++ d ++ " doesn't exist or isn't a directory"
1297 else verror ForceFiles msg
1299 checkDep :: PackageDBStack -> InstalledPackageId -> Validate ()
1300 checkDep db_stack pkgid
1301 | pkgid `elem` pkgids = return ()
1302 | otherwise = verror ForceAll ("dependency \"" ++ display pkgid
1303 ++ "\" doesn't exist")
1305 all_pkgs = allPackagesInStack db_stack
1306 pkgids = map installedPackageId all_pkgs
1308 checkDuplicateDepends :: [InstalledPackageId] -> Validate ()
1309 checkDuplicateDepends deps
1310 | null dups = return ()
1311 | otherwise = verror ForceAll ("package has duplicate dependencies: " ++
1312 unwords (map display dups))
1314 dups = [ p | (p:_:_) <- group (sort deps) ]
1316 checkHSLib :: [String] -> Bool -> String -> Validate ()
1317 checkHSLib dirs auto_ghci_libs lib = do
1318 let batch_lib_file = "lib" ++ lib ++ ".a"
1319 m <- liftIO $ doesFileExistOnPath batch_lib_file dirs
1321 Nothing -> verror ForceFiles ("cannot find " ++ batch_lib_file ++
1323 Just dir -> liftIO $ checkGHCiLib dir batch_lib_file lib auto_ghci_libs
1325 doesFileExistOnPath :: String -> [FilePath] -> IO (Maybe FilePath)
1326 doesFileExistOnPath file path = go path
1327 where go [] = return Nothing
1328 go (p:ps) = do b <- doesFileExistIn file p
1329 if b then return (Just p) else go ps
1331 doesFileExistIn :: String -> String -> IO Bool
1332 doesFileExistIn lib d
1333 | "$topdir" `isPrefixOf` d = return True
1334 | "$httptopdir" `isPrefixOf` d = return True
1335 | otherwise = doesFileExist (d </> lib)
1337 checkModules :: InstalledPackageInfo -> Validate ()
1338 checkModules pkg = do
1339 mapM_ findModule (exposedModules pkg ++ hiddenModules pkg)
1341 findModule modl = do
1342 -- there's no .hi file for GHC.Prim
1343 if modl == fromString "GHC.Prim" then return () else do
1344 let file = toFilePath modl <.> "hi"
1345 m <- liftIO $ doesFileExistOnPath file (importDirs pkg)
1346 when (isNothing m) $
1347 verror ForceFiles ("file " ++ file ++ " is missing")
1349 checkGHCiLib :: String -> String -> String -> Bool -> IO ()
1350 checkGHCiLib batch_lib_dir batch_lib_file lib auto_build
1351 | auto_build = autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
1352 | otherwise = return ()
1354 ghci_lib_file = lib <.> "o"
1356 -- automatically build the GHCi version of a batch lib,
1357 -- using ld --whole-archive.
1359 autoBuildGHCiLib :: String -> String -> String -> IO ()
1360 autoBuildGHCiLib dir batch_file ghci_file = do
1361 let ghci_lib_file = dir ++ '/':ghci_file
1362 batch_lib_file = dir ++ '/':batch_file
1363 hPutStr stderr ("building GHCi library " ++ ghci_lib_file ++ "...")
1364 #if defined(darwin_HOST_OS)
1365 r <- rawSystem "ld" ["-r","-x","-o",ghci_lib_file,"-all_load",batch_lib_file]
1366 #elif defined(mingw32_HOST_OS)
1367 execDir <- getLibDir
1368 r <- rawSystem (maybe "" (++"/gcc-lib/") execDir++"ld") ["-r","-x","-o",ghci_lib_file,"--whole-archive",batch_lib_file]
1370 r <- rawSystem "ld" ["-r","-x","-o",ghci_lib_file,"--whole-archive",batch_lib_file]
1372 when (r /= ExitSuccess) $ exitWith r
1373 hPutStrLn stderr (" done.")
1375 -- -----------------------------------------------------------------------------
1376 -- Searching for modules
1380 findModules :: [FilePath] -> IO [String]
1382 mms <- mapM searchDir paths
1385 searchDir path prefix = do
1386 fs <- getDirectoryEntries path `catch` \_ -> return []
1387 searchEntries path prefix fs
1389 searchEntries path prefix [] = return []
1390 searchEntries path prefix (f:fs)
1391 | looks_like_a_module = do
1392 ms <- searchEntries path prefix fs
1393 return (prefix `joinModule` f : ms)
1394 | looks_like_a_component = do
1395 ms <- searchDir (path </> f) (prefix `joinModule` f)
1396 ms' <- searchEntries path prefix fs
1399 searchEntries path prefix fs
1402 (base,suffix) = splitFileExt f
1403 looks_like_a_module =
1404 suffix `elem` haskell_suffixes &&
1405 all okInModuleName base
1406 looks_like_a_component =
1407 null suffix && all okInModuleName base
1413 -- ---------------------------------------------------------------------------
1414 -- expanding environment variables in the package configuration
1416 expandEnvVars :: String -> Force -> IO String
1417 expandEnvVars str0 force = go str0 ""
1419 go "" acc = return $! reverse acc
1420 go ('$':'{':str) acc | (var, '}':rest) <- break close str
1421 = do value <- lookupEnvVar var
1422 go rest (reverse value ++ acc)
1423 where close c = c == '}' || c == '\n' -- don't span newlines
1427 lookupEnvVar :: String -> IO String
1429 catch (System.Environment.getEnv nm)
1430 (\ _ -> do dieOrForceAll force ("Unable to expand variable " ++
1434 -----------------------------------------------------------------------------
1436 getProgramName :: IO String
1437 getProgramName = liftM (`withoutSuffix` ".bin") getProgName
1438 where str `withoutSuffix` suff
1439 | suff `isSuffixOf` str = take (length str - length suff) str
1442 bye :: String -> IO a
1443 bye s = putStr s >> exitWith ExitSuccess
1445 die :: String -> IO a
1448 dieWith :: Int -> String -> IO a
1451 prog <- getProgramName
1452 hPutStrLn stderr (prog ++ ": " ++ s)
1453 exitWith (ExitFailure ec)
1455 dieOrForceAll :: Force -> String -> IO ()
1456 dieOrForceAll ForceAll s = ignoreError s
1457 dieOrForceAll _other s = dieForcible s
1459 warn :: String -> IO ()
1462 ignoreError :: String -> IO ()
1463 ignoreError s = reportError (s ++ " (ignoring)")
1465 reportError :: String -> IO ()
1466 reportError s = do hFlush stdout; hPutStrLn stderr s
1468 dieForcible :: String -> IO ()
1469 dieForcible s = die (s ++ " (use --force to override)")
1471 my_head :: String -> [a] -> a
1472 my_head s [] = error s
1473 my_head _ (x : _) = x
1475 -----------------------------------------
1476 -- Cut and pasted from ghc/compiler/main/SysTools
1478 #if defined(mingw32_HOST_OS)
1479 subst :: Char -> Char -> String -> String
1480 subst a b ls = map (\ x -> if x == a then b else x) ls
1482 unDosifyPath :: FilePath -> FilePath
1483 unDosifyPath xs = subst '\\' '/' xs
1485 getLibDir :: IO (Maybe String)
1486 getLibDir = fmap (fmap (</> "lib")) $ getExecDir "/bin/ghc-pkg.exe"
1488 -- (getExecDir cmd) returns the directory in which the current
1489 -- executable, which should be called 'cmd', is running
1490 -- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
1491 -- you'll get "/a/b/c" back as the result
1492 getExecDir :: String -> IO (Maybe String)
1494 getExecPath >>= maybe (return Nothing) removeCmdSuffix
1495 where initN n = reverse . drop n . reverse
1496 removeCmdSuffix = return . Just . initN (length cmd) . unDosifyPath
1498 getExecPath :: IO (Maybe String)
1500 allocaArray len $ \buf -> do
1501 ret <- getModuleFileName nullPtr buf len
1502 if ret == 0 then return Nothing
1503 else liftM Just $ peekCString buf
1504 where len = 2048 -- Plenty, PATH_MAX is 512 under Win32.
1506 foreign import stdcall unsafe "GetModuleFileNameA"
1507 getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
1510 getLibDir :: IO (Maybe String)
1511 getLibDir = return Nothing
1514 -----------------------------------------
1515 -- Adapted from ghc/compiler/utils/Panic
1517 installSignalHandlers :: IO ()
1518 installSignalHandlers = do
1519 threadid <- myThreadId
1521 interrupt = Exception.throwTo threadid
1522 (Exception.ErrorCall "interrupted")
1524 #if !defined(mingw32_HOST_OS)
1525 _ <- installHandler sigQUIT (Catch interrupt) Nothing
1526 _ <- installHandler sigINT (Catch interrupt) Nothing
1529 -- GHC 6.3+ has support for console events on Windows
1530 -- NOTE: running GHCi under a bash shell for some reason requires
1531 -- you to press Ctrl-Break rather than Ctrl-C to provoke
1532 -- an interrupt. Ctrl-C is getting blocked somewhere, I don't know
1533 -- why --SDM 17/12/2004
1534 let sig_handler ControlC = interrupt
1535 sig_handler Break = interrupt
1536 sig_handler _ = return ()
1538 _ <- installHandler (Catch sig_handler)
1542 #if mingw32_HOST_OS || mingw32_TARGET_OS
1543 throwIOIO :: Exception.IOException -> IO a
1544 throwIOIO = Exception.throwIO
1546 catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a
1547 catchIO = Exception.catch
1550 catchError :: IO a -> (String -> IO a) -> IO a
1551 catchError io handler = io `Exception.catch` handler'
1552 where handler' (Exception.ErrorCall err) = handler err
1555 writeBinaryFileAtomic :: Bin.Binary a => FilePath -> a -> IO ()
1556 writeBinaryFileAtomic targetFile obj =
1557 withFileAtomic targetFile $ \h -> do
1558 hSetBinaryMode h True
1559 B.hPutStr h (Bin.encode obj)
1561 writeFileUtf8Atomic :: FilePath -> String -> IO ()
1562 writeFileUtf8Atomic targetFile content =
1563 withFileAtomic targetFile $ \h -> do
1564 #if __GLASGOW_HASKELL__ >= 612
1569 -- copied from Cabal's Distribution.Simple.Utils, except that we want
1570 -- to use text files here, rather than binary files.
1571 withFileAtomic :: FilePath -> (Handle -> IO ()) -> IO ()
1572 withFileAtomic targetFile write_content = do
1573 (newFile, newHandle) <- openNewFile targetDir template
1574 do write_content newHandle
1576 #if mingw32_HOST_OS || mingw32_TARGET_OS
1577 renameFile newFile targetFile
1578 -- If the targetFile exists then renameFile will fail
1579 `catchIO` \err -> do
1580 exists <- doesFileExist targetFile
1582 then do removeFileSafe targetFile
1583 -- Big fat hairy race condition
1584 renameFile newFile targetFile
1585 -- If the removeFile succeeds and the renameFile fails
1586 -- then we've lost the atomic property.
1589 renameFile newFile targetFile
1591 `Exception.onException` do hClose newHandle
1592 removeFileSafe newFile
1594 template = targetName <.> "tmp"
1595 targetDir | null targetDir_ = "."
1596 | otherwise = targetDir_
1597 --TODO: remove this when takeDirectory/splitFileName is fixed
1598 -- to always return a valid dir
1599 (targetDir_,targetName) = splitFileName targetFile
1601 openNewFile :: FilePath -> String -> IO (FilePath, Handle)
1602 openNewFile dir template = do
1603 #if __GLASGOW_HASKELL__ >= 612
1604 -- this was added to System.IO in 6.12.1
1605 -- we must use this version because the version below opens the file
1607 openTempFileWithDefaultPermissions dir template
1609 -- Ugh, this is a copy/paste of code from the base library, but
1610 -- if uses 666 rather than 600 for the permissions.
1614 -- We split off the last extension, so we can use .foo.ext files
1615 -- for temporary files (hidden on Unix OSes). Unfortunately we're
1616 -- below filepath in the hierarchy here.
1618 case break (== '.') $ reverse template of
1619 -- First case: template contains no '.'s. Just re-reverse it.
1620 (rev_suffix, "") -> (reverse rev_suffix, "")
1621 -- Second case: template contains at least one '.'. Strip the
1622 -- dot from the prefix and prepend it to the suffix (if we don't
1623 -- do this, the unique number will get added after the '.' and
1624 -- thus be part of the extension, which is wrong.)
1625 (rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
1626 -- Otherwise, something is wrong, because (break (== '.')) should
1627 -- always return a pair with either the empty string or a string
1628 -- beginning with '.' as the second component.
1629 _ -> error "bug in System.IO.openTempFile"
1631 oflags = rw_flags .|. o_EXCL
1633 withFilePath = withCString
1636 fd <- withFilePath filepath $ \ f ->
1637 c_open f oflags 0o666
1642 then findTempName (x+1)
1643 else ioError (errnoToIOError "openNewBinaryFile" errno Nothing (Just dir))
1645 -- XXX We want to tell fdToHandle what the filepath is,
1646 -- as any exceptions etc will only be able to report the
1650 `Exception.onException` c_close fd
1651 return (filepath, h)
1653 filename = prefix ++ show x ++ suffix
1654 filepath = dir `combine` filename
1656 -- XXX Copied from GHC.Handle
1657 std_flags, output_flags, rw_flags :: CInt
1658 std_flags = o_NONBLOCK .|. o_NOCTTY
1659 output_flags = std_flags .|. o_CREAT
1660 rw_flags = output_flags .|. o_RDWR
1661 #endif /* GLASGOW_HASKELL < 612 */
1663 -- | The function splits the given string to substrings
1664 -- using 'isSearchPathSeparator'.
1665 parseSearchPath :: String -> [FilePath]
1666 parseSearchPath path = split path
1668 split :: String -> [String]
1672 _:rest -> chunk : split rest
1676 #ifdef mingw32_HOST_OS
1677 ('\"':xs@(_:_)) | last xs == '\"' -> init xs
1681 (chunk', rest') = break isSearchPathSeparator s
1683 readUTF8File :: FilePath -> IO String
1684 readUTF8File file = do
1685 h <- openFile file ReadMode
1686 #if __GLASGOW_HASKELL__ >= 612
1687 -- fix the encoding to UTF-8
1692 -- removeFileSave doesn't throw an exceptions, if the file is already deleted
1693 removeFileSafe :: FilePath -> IO ()
1695 removeFile fn `catch` \ e ->
1696 when (not $ isDoesNotExistError e) $ ioError e