fix some problems with wired-in packages
[ghc-hetmet.git] / compiler / main / Packages.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section{Package manipulation}
5
6 \begin{code}
7 module Packages (
8         module PackageConfig,
9
10         -- * The PackageConfigMap
11         PackageConfigMap, emptyPackageConfigMap, lookupPackage,
12         extendPackageConfigMap, dumpPackages,
13
14         -- * Reading the package config, and processing cmdline args
15         PackageState(..),
16         initPackages,
17         getPackageDetails,
18         lookupModuleInAllPackages,
19
20         -- * Inspecting the set of packages in scope
21         getPackageIncludePath,
22         getPackageCIncludes,
23         getPackageLibraryPath,
24         getPackageLinkOpts,
25         getPackageExtraCcOpts,
26         getPackageFrameworkPath,
27         getPackageFrameworks,
28         getExplicitPackagesAnd,
29
30         -- * Utils
31         isDllName
32     )
33 where
34
35 #include "HsVersions.h"
36
37 import PackageConfig    
38 import SysTools         ( getTopDir, getPackageConfigPath )
39 import ParsePkgConf     ( loadPackageConfig )
40 import DynFlags         ( dopt, DynFlag(..), DynFlags(..), PackageFlag(..) )
41 import StaticFlags      ( opt_Static )
42 import Config           ( cProjectVersion )
43 import Name             ( Name, nameModule_maybe )
44 import UniqFM
45 import Module
46 import UniqSet
47 import Util
48 import Maybes           ( expectJust, MaybeErr(..) )
49 import Panic
50 import Outputable
51
52 #if __GLASGOW_HASKELL__ >= 603
53 import System.Directory ( getAppUserDataDirectory )
54 #else
55 import Compat.Directory ( getAppUserDataDirectory )
56 #endif
57
58 import System.Environment ( getEnv )
59 import Distribution.InstalledPackageInfo
60 import Distribution.Package
61 import Distribution.Version
62 import System.Directory ( doesFileExist, doesDirectoryExist,
63                           getDirectoryContents )
64 import Data.Maybe       ( catMaybes )
65 import Control.Monad    ( foldM )
66 import Data.List        ( nub, partition, sortBy, isSuffixOf )
67 import FastString
68 import EXCEPTION        ( throwDyn )
69 import ErrUtils         ( debugTraceMsg, putMsg, Message )
70
71 -- ---------------------------------------------------------------------------
72 -- The Package state
73
74 -- Package state is all stored in DynFlags, including the details of
75 -- all packages, which packages are exposed, and which modules they
76 -- provide.
77
78 -- The package state is computed by initPackages, and kept in DynFlags.
79 --
80 --   * -package <pkg> causes <pkg> to become exposed, and all other packages 
81 --      with the same name to become hidden.
82 -- 
83 --   * -hide-package <pkg> causes <pkg> to become hidden.
84 -- 
85 --   * Let exposedPackages be the set of packages thus exposed.  
86 --     Let depExposedPackages be the transitive closure from exposedPackages of
87 --     their dependencies.
88 --
89 --   * When searching for a module from an explicit import declaration,
90 --     only the exposed modules in exposedPackages are valid.
91 --
92 --   * When searching for a module from an implicit import, all modules
93 --     from depExposedPackages are valid.
94 --
95 --   * When linking in a comp manager mode, we link in packages the
96 --     program depends on (the compiler knows this list by the
97 --     time it gets to the link step).  Also, we link in all packages
98 --     which were mentioned with explicit -package flags on the command-line,
99 --     or are a transitive dependency of same, or are "base"/"rts".
100 --     The reason for (b) is that we might need packages which don't
101 --     contain any Haskell modules, and therefore won't be discovered
102 --     by the normal mechanism of dependency tracking.
103
104 -- Notes on DLLs
105 -- ~~~~~~~~~~~~~
106 -- When compiling module A, which imports module B, we need to 
107 -- know whether B will be in the same DLL as A.  
108 --      If it's in the same DLL, we refer to B_f_closure
109 --      If it isn't, we refer to _imp__B_f_closure
110 -- When compiling A, we record in B's Module value whether it's
111 -- in a different DLL, by setting the DLL flag.
112
113 data PackageState = PackageState {
114
115   explicitPackages      :: [PackageId],
116         -- The packages we're going to link in eagerly.  This list
117         -- should be in reverse dependency order; that is, a package
118         -- is always mentioned before the packages it depends on.
119
120   origPkgIdMap          :: PackageConfigMap, -- PackageId   -> PackageConfig
121         -- the full package database
122
123   pkgIdMap              :: PackageConfigMap, -- PackageId   -> PackageConfig
124         -- Derived from origPkgIdMap.
125         -- The exposed flags are adjusted according to -package and
126         -- -hide-package flags, and -ignore-package removes packages.
127
128   moduleToPkgConfAll    :: UniqFM [(PackageConfig,Bool)] -- ModuleEnv mapping
129         -- Derived from pkgIdMap.       
130         -- Maps Module to (pkgconf,exposed), where pkgconf is the
131         -- PackageConfig for the package containing the module, and
132         -- exposed is True if the package exposes that module.
133   }
134
135 -- A PackageConfigMap maps a PackageId to a PackageConfig
136 type PackageConfigMap = UniqFM PackageConfig
137
138 emptyPackageConfigMap :: PackageConfigMap
139 emptyPackageConfigMap = emptyUFM
140
141 lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig
142 lookupPackage = lookupUFM
143
144 extendPackageConfigMap
145    :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap
146 extendPackageConfigMap pkg_map new_pkgs 
147   = foldl add pkg_map new_pkgs
148   where add pkg_map p = addToUFM pkg_map (packageConfigId p) p
149
150 getPackageDetails :: PackageState -> PackageId -> PackageConfig
151 getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkgIdMap dflags) ps)
152
153 -- ----------------------------------------------------------------------------
154 -- Loading the package config files and building up the package state
155
156 -- | Call this after parsing the DynFlags.  It reads the package
157 -- configuration files, and sets up various internal tables of package
158 -- information, according to the package-related flags on the
159 -- command-line (@-package@, @-hide-package@ etc.)
160 initPackages :: DynFlags -> IO DynFlags
161 initPackages dflags = do 
162   pkg_map <- readPackageConfigs dflags; 
163   mkPackageState dflags pkg_map
164
165 -- -----------------------------------------------------------------------------
166 -- Reading the package database(s)
167
168 readPackageConfigs :: DynFlags -> IO PackageConfigMap
169 readPackageConfigs dflags = do
170    e_pkg_path <- try (getEnv "GHC_PACKAGE_PATH")
171    system_pkgconfs <- getSystemPackageConfigs dflags
172
173    let pkgconfs = case e_pkg_path of
174                     Left _   -> system_pkgconfs
175                     Right path
176                      | last cs == "" -> init cs ++ system_pkgconfs
177                      | otherwise     -> cs
178                      where cs = parseSearchPath path
179                      -- if the path ends in a separator (eg. "/foo/bar:")
180                      -- the we tack on the system paths.
181
182         -- Read all the ones mentioned in -package-conf flags
183    pkg_map <- foldM (readPackageConfig dflags) emptyPackageConfigMap
184                  (reverse pkgconfs ++ extraPkgConfs dflags)
185
186    return pkg_map
187
188
189 getSystemPackageConfigs :: DynFlags -> IO [FilePath]
190 getSystemPackageConfigs dflags = do
191         -- System one always comes first
192    system_pkgconf <- getPackageConfigPath
193
194         -- allow package.conf.d to contain a bunch of .conf files
195         -- containing package specifications.  This is an easier way
196         -- to maintain the package database on systems with a package
197         -- management system, or systems that don't want to run ghc-pkg
198         -- to register or unregister packages.  Undocumented feature for now.
199    let system_pkgconf_dir = system_pkgconf ++ ".d"
200    system_pkgconf_dir_exists <- doesDirectoryExist system_pkgconf_dir
201    system_pkgconfs <-
202      if system_pkgconf_dir_exists
203        then do files <- getDirectoryContents system_pkgconf_dir
204                return [ system_pkgconf_dir ++ '/' : file
205                       | file <- files
206                       , isSuffixOf ".conf" file]
207        else return []
208
209         -- Read user's package conf (eg. ~/.ghc/i386-linux-6.3/package.conf)
210         -- unless the -no-user-package-conf flag was given.
211         -- We only do this when getAppUserDataDirectory is available 
212         -- (GHC >= 6.3).
213    user_pkgconf <- handle (\_ -> return []) $ do
214       appdir <- getAppUserDataDirectory "ghc"
215       let 
216          pkgconf = appdir
217                    `joinFileName` (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion)
218                    `joinFileName` "package.conf"
219       flg <- doesFileExist pkgconf
220       if (flg && dopt Opt_ReadUserPackageConf dflags)
221         then return [pkgconf]
222         else return []
223
224    return (user_pkgconf ++ system_pkgconfs ++ [system_pkgconf])
225
226
227 readPackageConfig
228    :: DynFlags -> PackageConfigMap -> FilePath -> IO PackageConfigMap
229 readPackageConfig dflags pkg_map conf_file = do
230   debugTraceMsg dflags 2 (text "Using package config file:" <+> text conf_file)
231   proto_pkg_configs <- loadPackageConfig conf_file
232   top_dir           <- getTopDir
233   let pkg_configs1 = mungePackagePaths top_dir proto_pkg_configs
234       pkg_configs2 = maybeHidePackages dflags pkg_configs1
235   return (extendPackageConfigMap pkg_map pkg_configs2)
236
237 maybeHidePackages :: DynFlags -> [PackageConfig] -> [PackageConfig]
238 maybeHidePackages dflags pkgs
239   | dopt Opt_HideAllPackages dflags = map hide pkgs
240   | otherwise                       = pkgs
241   where
242     hide pkg = pkg{ exposed = False }
243
244 mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig]
245 -- Replace the string "$topdir" at the beginning of a path
246 -- with the current topdir (obtained from the -B option).
247 mungePackagePaths top_dir ps = map munge_pkg ps
248  where 
249   munge_pkg p = p{ importDirs  = munge_paths (importDirs p),
250                    includeDirs = munge_paths (includeDirs p),
251                    libraryDirs = munge_paths (libraryDirs p),
252                    frameworkDirs = munge_paths (frameworkDirs p) }
253
254   munge_paths = map munge_path
255
256   munge_path p 
257           | Just p' <- maybePrefixMatch "$topdir" p = top_dir ++ p'
258           | otherwise                               = p
259
260
261 -- -----------------------------------------------------------------------------
262 -- When all the command-line options are in, we can process our package
263 -- settings and populate the package state.
264
265 mkPackageState :: DynFlags -> PackageConfigMap -> IO DynFlags
266 mkPackageState dflags orig_pkg_db = do
267   --
268   -- Modify the package database according to the command-line flags
269   -- (-package, -hide-package, -ignore-package, -hide-all-packages).
270   --
271   -- Also, here we build up a set of the packages mentioned in -package
272   -- flags on the command line; these are called the "explicit" packages.
273   -- we link these packages in eagerly.  The explicit set should contain
274   -- at least rts & base, which is why we pretend that the command line
275   -- contains -package rts & -package base.
276   --
277   let
278         flags = reverse (packageFlags dflags)
279
280         procflags pkgs expl [] = return (pkgs,expl)
281         procflags pkgs expl (ExposePackage str : flags) = do
282            case pick str pkgs of
283                 Nothing -> missingPackageErr str
284                 Just (p,ps) -> procflags (p':ps') expl' flags
285                   where p' = p {exposed=True}
286                         ps' = hideAll (pkgName (package p)) ps
287                         expl' = package p : expl
288         procflags pkgs expl (HidePackage str : flags) = do
289            case partition (matches str) pkgs of
290                 ([],_)   -> missingPackageErr str
291                 (ps,qs) -> procflags (map hide ps ++ qs) expl flags
292                   where hide p = p {exposed=False}
293         procflags pkgs expl (IgnorePackage str : flags) = do
294            case partition (matches str) pkgs of
295                 (ps,qs) -> procflags qs expl flags
296                 -- missing package is not an error for -ignore-package,
297                 -- because a common usage is to -ignore-package P as
298                 -- a preventative measure just in case P exists.
299
300         pick str pkgs
301           = case partition (matches str) pkgs of
302                 ([],_) -> Nothing
303                 (ps,rest) -> 
304                    case sortByVersion ps of
305                         (p:ps) -> Just (p, ps ++ rest)
306                         _ -> panic "Packages.pick"
307
308         sortByVersion = sortBy (flip (comparing (pkgVersion.package)))
309         comparing f a b = f a `compare` f b
310
311         -- A package named on the command line can either include the
312         -- version, or just the name if it is unambiguous.
313         matches str p
314                 =  str == showPackageId (package p)
315                 || str == pkgName (package p)
316
317         -- When a package is requested to be exposed, we hide all other
318         -- packages with the same name.
319         hideAll name ps = map maybe_hide ps
320           where maybe_hide p | pkgName (package p) == name = p {exposed=False}
321                              | otherwise                   = p
322   --
323   (pkgs1,explicit) <- procflags (eltsUFM orig_pkg_db) [] flags
324   --
325   -- hide all packages for which there is also a later version
326   -- that is already exposed.  This just makes it non-fatal to have two
327   -- versions of a package exposed, which can happen if you install a
328   -- later version of a package in the user database, for example.
329   --
330   let maybe_hide p
331            | not (exposed p) = return p
332            | (p' : _) <- later_versions = do
333                 debugTraceMsg dflags 2 $
334                    (ptext SLIT("hiding package") <+> text (showPackageId (package p)) <+>
335                     ptext SLIT("to avoid conflict with later version") <+>
336                     text (showPackageId (package p')))
337                 return (p {exposed=False})
338            | otherwise = return p
339           where myname = pkgName (package p)
340                 myversion = pkgVersion (package p)
341                 later_versions = [ p | p <- pkgs1, exposed p,
342                                     let pkg = package p,
343                                     pkgName pkg == myname,
344                                     pkgVersion pkg > myversion ]
345
346   pkgs2 <- mapM maybe_hide pkgs1
347   --
348   -- Now we must find our wired-in packages, and rename them to
349   -- their canonical names (eg. base-1.0 ==> base).
350   --
351   let
352         wired_in_pkgids = [ basePackageId,
353                             rtsPackageId,
354                             haskell98PackageId,
355                             thPackageId ]
356
357         wired_in_names = map packageIdString wired_in_pkgids
358
359         -- find which package corresponds to each wired-in package
360         -- delete any other packages with the same name
361         -- update the package and any dependencies to point to the new
362         -- one.
363         --
364         -- When choosing which package to map to a wired-in package
365         -- name, we prefer exposed packages, and pick the latest
366         -- version.  To override the default choice, -hide-package
367         -- could be used to hide newer versions.
368         --
369         findWiredInPackage :: [PackageConfig] -> String
370                            -> IO (Maybe PackageIdentifier)
371         findWiredInPackage pkgs wired_pkg =
372            let all_ps = [ p | p <- pkgs, pkgName (package p) == wired_pkg ] in
373            case filter exposed all_ps of
374                 [] -> case all_ps of
375                         []   -> notfound
376                         many -> pick (head (sortByVersion many))
377                 many  -> pick (head (sortByVersion many))
378           where
379                 notfound = do
380                           debugTraceMsg dflags 2 $
381                             ptext SLIT("wired-in package ")
382                                  <> text wired_pkg
383                                  <> ptext SLIT(" not found.")
384                           return Nothing
385                 pick pkg = do
386                         debugTraceMsg dflags 2 $
387                             ptext SLIT("wired-in package ")
388                                  <> text wired_pkg
389                                  <> ptext SLIT(" mapped to ")
390                                  <> text (showPackageId (package pkg))
391                         return (Just (package pkg))
392
393
394   mb_wired_in_ids <- mapM (findWiredInPackage pkgs2) wired_in_names
395   let 
396         wired_in_ids = catMaybes mb_wired_in_ids
397
398         deleteOtherWiredInPackages pkgs = filter ok pkgs
399           where ok p = pkgName (package p) `notElem` wired_in_names
400                      || package p `elem` wired_in_ids
401
402         updateWiredInDependencies pkgs = map upd_pkg pkgs
403           where upd_pkg p = p{ package = upd_pid (package p),
404                                depends = map upd_pid (depends p) }
405
406         upd_pid pid = case filter (== pid) wired_in_ids of
407                                 [] -> pid
408                                 (x:_) -> x{ pkgVersion = Version [] [] }
409
410         pkgs3 = deleteOtherWiredInPackages pkgs2
411
412         pkgs4 = updateWiredInDependencies pkgs3
413
414         explicit1 = map upd_pid explicit
415
416         -- we must return an updated thisPackage, just in case we
417         -- are actually compiling one of the wired-in packages
418         Just old_this_pkg = unpackPackageId (thisPackage dflags)
419         new_this_pkg = mkPackageId (upd_pid old_this_pkg)
420
421   --
422   -- Eliminate any packages which have dangling dependencies (perhaps
423   -- because the package was removed by -ignore-package).
424   --
425   let
426         elimDanglingDeps pkgs = 
427            case partition (not.null.snd) (map (getDanglingDeps pkgs) pkgs) of
428               ([],ps) -> return (map fst ps)
429               (ps,qs) -> do
430                  mapM_ reportElim ps
431                  elimDanglingDeps (map fst qs)
432
433         reportElim (p, deps) = 
434                 debugTraceMsg dflags 2 $
435                    (ptext SLIT("package") <+> pprPkg p <+> 
436                         ptext SLIT("will be ignored due to missing dependencies:") $$ 
437                     nest 2 (hsep (map (text.showPackageId) deps)))
438
439         getDanglingDeps pkgs p = (p, filter dangling (depends p))
440           where dangling pid = pid `notElem` all_pids
441                 all_pids = map package pkgs
442   --
443   pkgs <- elimDanglingDeps pkgs4
444   let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs
445   --
446   -- Find the transitive closure of dependencies of exposed
447   --
448   let exposed_pkgids = [ packageConfigId p | p <- pkgs, exposed p ]
449   dep_exposed <- closeDeps pkg_db exposed_pkgids
450   let
451         -- add base & rts to the explicit packages
452         basicLinkedPackages = filter (flip elemUFM pkg_db)
453                                  [basePackageId,rtsPackageId]
454         explicit2 = addListToUniqSet (mkUniqSet (map mkPackageId explicit1))
455                                      basicLinkedPackages
456   --
457   -- Close the explicit packages with their dependencies
458   --
459   dep_explicit <- closeDeps pkg_db (uniqSetToList explicit2)
460   --
461   -- Build up a mapping from Module -> PackageConfig for all modules.
462   -- Discover any conflicts at the same time, and factor in the new exposed
463   -- status of each package.
464   --
465   let mod_map = mkModuleMap pkg_db dep_exposed
466
467       pstate = PackageState{ explicitPackages     = dep_explicit,
468                              origPkgIdMap           = orig_pkg_db,
469                              pkgIdMap               = pkg_db,
470                              moduleToPkgConfAll   = mod_map
471                            }
472
473   return dflags{ pkgState = pstate, thisPackage = new_this_pkg }
474   -- done!
475
476
477 mkModuleMap
478   :: PackageConfigMap
479   -> [PackageId]
480   -> UniqFM [(PackageConfig, Bool)]
481 mkModuleMap pkg_db pkgs = foldr extend_modmap emptyUFM pkgs
482   where
483         extend_modmap pkgid modmap =
484                 addListToUFM_C (++) modmap 
485                     [(m, [(pkg, m `elem` exposed_mods)]) | m <- all_mods]
486           where
487                 pkg = expectJust "mkModuleMap" (lookupPackage pkg_db pkgid)
488                 exposed_mods = map mkModuleName (exposedModules pkg)
489                 hidden_mods  = map mkModuleName (hiddenModules pkg)
490                 all_mods = exposed_mods ++ hidden_mods
491
492 pprPkg :: PackageConfig -> SDoc
493 pprPkg p = text (showPackageId (package p))
494
495 -- -----------------------------------------------------------------------------
496 -- Extracting information from the packages in scope
497
498 -- Many of these functions take a list of packages: in those cases,
499 -- the list is expected to contain the "dependent packages",
500 -- i.e. those packages that were found to be depended on by the
501 -- current module/program.  These can be auto or non-auto packages, it
502 -- doesn't really matter.  The list is always combined with the list
503 -- of explicit (command-line) packages to determine which packages to
504 -- use.
505
506 getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String]
507 getPackageIncludePath dflags pkgs = do
508   ps <- getExplicitPackagesAnd dflags pkgs
509   return (nub (filter notNull (concatMap includeDirs ps)))
510
511         -- includes are in reverse dependency order (i.e. rts first)
512 getPackageCIncludes :: [PackageConfig] -> IO [String]
513 getPackageCIncludes pkg_configs = do
514   return (reverse (nub (filter notNull (concatMap includes pkg_configs))))
515
516 getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String]
517 getPackageLibraryPath dflags pkgs = do 
518   ps <- getExplicitPackagesAnd dflags pkgs
519   return (nub (filter notNull (concatMap libraryDirs ps)))
520
521 getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String]
522 getPackageLinkOpts dflags pkgs = do
523   ps <- getExplicitPackagesAnd dflags pkgs
524   let tag = buildTag dflags
525       rts_tag = rtsBuildTag dflags
526   let 
527         imp        = if opt_Static then "" else "_dyn"
528         libs p     = map ((++imp) . addSuffix) (hsLibraries p)
529                          ++ hACK_dyn (extraLibraries p)
530         all_opts p = map ("-l" ++) (libs p) ++ ldOptions p
531
532         suffix     = if null tag then "" else  '_':tag
533         rts_suffix = if null rts_tag then "" else  '_':rts_tag
534
535         addSuffix rts@"HSrts"    = rts       ++ rts_suffix
536         addSuffix other_lib      = other_lib ++ suffix
537
538         -- This is a hack that's even more horrible (and hopefully more temporary)
539         -- than the one below [referring to previous splittage of HSbase into chunks
540         -- to work around GNU ld bug]. HSbase_cbits and friends require the _dyn suffix
541         -- for dynamic linking, but not _p or other 'way' suffix. So we just add
542         -- _dyn to extraLibraries if they already have a _cbits suffix.
543         
544         hACK_dyn = map hack
545           where hack lib | not opt_Static && "_cbits" `isSuffixOf` lib = lib ++ "_dyn"
546                          | otherwise = lib
547
548   return (concat (map all_opts ps))
549
550 getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String]
551 getPackageExtraCcOpts dflags pkgs = do
552   ps <- getExplicitPackagesAnd dflags pkgs
553   return (concatMap ccOptions ps)
554
555 getPackageFrameworkPath  :: DynFlags -> [PackageId] -> IO [String]
556 getPackageFrameworkPath dflags pkgs = do
557   ps <- getExplicitPackagesAnd dflags pkgs
558   return (nub (filter notNull (concatMap frameworkDirs ps)))
559
560 getPackageFrameworks  :: DynFlags -> [PackageId] -> IO [String]
561 getPackageFrameworks dflags pkgs = do
562   ps <- getExplicitPackagesAnd dflags pkgs
563   return (concatMap frameworks ps)
564
565 -- -----------------------------------------------------------------------------
566 -- Package Utils
567
568 -- | Takes a Module, and if the module is in a package returns 
569 -- @(pkgconf,exposed)@ where pkgconf is the PackageConfig for that package,
570 -- and exposed is True if the package exposes the module.
571 lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(PackageConfig,Bool)]
572 lookupModuleInAllPackages dflags m =
573   case lookupUFM (moduleToPkgConfAll (pkgState dflags)) m of
574         Nothing -> []
575         Just ps -> ps
576
577 getExplicitPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig]
578 getExplicitPackagesAnd dflags pkgids =
579   let 
580       state   = pkgState dflags
581       pkg_map = pkgIdMap state
582       expl    = explicitPackages state
583   in do
584   all_pkgs <- throwErr (foldM (add_package pkg_map) expl pkgids)
585   return (map (getPackageDetails state) all_pkgs)
586
587 -- Takes a list of packages, and returns the list with dependencies included,
588 -- in reverse dependency order (a package appears before those it depends on).
589 closeDeps :: PackageConfigMap -> [PackageId] -> IO [PackageId]
590 closeDeps pkg_map ps = throwErr (closeDepsErr pkg_map ps)
591
592 throwErr :: MaybeErr Message a -> IO a
593 throwErr m = case m of
594                 Failed e    -> throwDyn (CmdLineError (showSDoc e))
595                 Succeeded r -> return r
596
597 closeDepsErr :: PackageConfigMap -> [PackageId]
598         -> MaybeErr Message [PackageId]
599 closeDepsErr pkg_map ps = foldM (add_package pkg_map) [] ps
600
601 -- internal helper
602 add_package :: PackageConfigMap -> [PackageId] -> PackageId 
603         -> MaybeErr Message [PackageId]
604 add_package pkg_db ps p
605   | p `elem` ps = return ps     -- Check if we've already added this package
606   | otherwise =
607       case lookupPackage pkg_db p of
608         Nothing -> Failed (missingPackageMsg (packageIdString p))
609         Just pkg -> do
610            -- Add the package's dependents also
611            let deps = map mkPackageId (depends pkg)
612            ps' <- foldM (add_package pkg_db) ps deps
613            return (p : ps')
614
615 missingPackageErr p = throwDyn (CmdLineError (showSDoc (missingPackageMsg p)))
616 missingPackageMsg p = ptext SLIT("unknown package:") <+> text p
617
618 -- -----------------------------------------------------------------------------
619
620 isDllName :: PackageId -> Name -> Bool
621 isDllName this_pkg name
622   | opt_Static = False
623   | Just mod <- nameModule_maybe name = modulePackageId mod /= this_pkg
624   | otherwise = False  -- no, it is not even an external name
625
626 -- -----------------------------------------------------------------------------
627 -- Displaying packages
628
629 dumpPackages :: DynFlags -> IO ()
630 -- Show package info on console, if verbosity is >= 3
631 dumpPackages dflags
632   = do  let pkg_map = pkgIdMap (pkgState dflags)
633         putMsg dflags $
634               vcat (map (text.showInstalledPackageInfo) (eltsUFM pkg_map))
635 \end{code}