[project @ 2005-05-17 10:51:04 by simonmar]
[ghc-hetmet.git] / ghc / 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         PackageIdH(..), isHomePackage,
16         PackageState(..), 
17         initPackages,
18         moduleToPackageConfig,
19         getPackageDetails,
20         isHomeModule,
21
22         -- * Inspecting the set of packages in scope
23         getPackageIncludePath,
24         getPackageCIncludes,
25         getPackageLibraryPath,
26         getPackageLinkOpts,
27         getPackageExtraCcOpts,
28         getPackageFrameworkPath,
29         getPackageFrameworks,
30         getExplicitPackagesAnd,
31
32         -- * Utils
33         isDllName
34     )
35 where
36
37 #include "HsVersions.h"
38
39 import PackageConfig    
40 import SysTools         ( getTopDir, getPackageConfigPath )
41 import ParsePkgConf     ( loadPackageConfig )
42 import DynFlags         ( dopt, DynFlag(..), DynFlags(..), PackageFlag(..) )
43 import StaticFlags      ( opt_Static )
44 import Config           ( cProjectVersion )
45 import Name             ( Name, nameModule_maybe )
46 import Module           ( Module, mkModule )
47 import UniqFM
48 import UniqSet
49 import Util
50 import Maybes           ( expectJust )
51 import Panic
52 import Outputable
53
54 #if __GLASGOW_HASKELL__ >= 603
55 import System.Directory ( getAppUserDataDirectory )
56 #else
57 import Compat.Directory ( getAppUserDataDirectory )
58 #endif
59
60 import Distribution.InstalledPackageInfo
61 import Distribution.Package
62 import Distribution.Version
63 import Data.Maybe       ( isNothing )
64 import System.Directory ( doesFileExist )
65 import Control.Monad    ( when, foldM )
66 import Data.List        ( nub, partition )
67
68 #ifdef mingw32_TARGET_OS
69 import Data.List        ( isPrefixOf )
70 #endif
71
72 import FastString
73 import DATA_IOREF
74 import EXCEPTION        ( throwDyn )
75 import ErrUtils         ( debugTraceMsg, putMsg )
76
77 -- ---------------------------------------------------------------------------
78 -- The Package state
79
80 -- Package state is all stored in DynFlags, including the details of
81 -- all packages, which packages are exposed, and which modules they
82 -- provide.
83
84 -- The package state is computed by initPackages, and kept in DynFlags.
85 --
86 --   * -package <pkg> causes <pkg> to become exposed, and all other packages 
87 --      with the same name to become hidden.
88 -- 
89 --   * -hide-package <pkg> causes <pkg> to become hidden.
90 -- 
91 --   * Let exposedPackages be the set of packages thus exposed.  
92 --     Let depExposedPackages be the transitive closure from exposedPackages of
93 --     their dependencies.
94 --
95 --   * It is an error for any two packages in depExposedPackages to provide the
96 --     same module.
97 -- 
98 --   * When searching for a module from an explicit import declaration,
99 --     only the exposed modules in exposedPackages are valid.
100 --
101 --   * When searching for a module from an implicit import, all modules
102 --     from depExposedPackages are valid.
103 --
104 --   * When linking in a comp manager mode, we link in packages the
105 --     program depends on (the compiler knows this list by the
106 --     time it gets to the link step).  Also, we link in all packages
107 --     which were mentioned with explicit -package flags on the command-line,
108 --     or are a transitive dependency of same, or are "base"/"rts".
109 --     The reason for (b) is that we might need packages which don't
110 --     contain any Haskell modules, and therefore won't be discovered
111 --     by the normal mechanism of dependency tracking.
112
113
114 -- One important thing that the package state provides is a way to
115 -- tell, for a given module, whether it is part of the current package
116 -- or not.  We need to know this for two reasons:
117 --
118 --  * generating cross-DLL calls is different from intra-DLL calls 
119 --    (see below).
120 --  * we don't record version information in interface files for entities
121 --    in a different package.
122 -- 
123 -- Notes on DLLs
124 -- ~~~~~~~~~~~~~
125 -- When compiling module A, which imports module B, we need to 
126 -- know whether B will be in the same DLL as A.  
127 --      If it's in the same DLL, we refer to B_f_closure
128 --      If it isn't, we refer to _imp__B_f_closure
129 -- When compiling A, we record in B's Module value whether it's
130 -- in a different DLL, by setting the DLL flag.
131
132 data PackageState = PackageState {
133
134   explicitPackages      :: [PackageId],
135         -- The packages we're going to link in eagerly.  This list
136         -- should be in reverse dependency order; that is, a package
137         -- is always mentioned before the packages it depends on.
138
139   pkgIdMap              :: PackageConfigMap, -- PackageId   -> PackageConfig
140         -- mapping derived from the package databases and
141         -- command-line package flags.
142
143   moduleToPkgConf       :: UniqFM (PackageConfig,Bool),
144         -- Maps Module to (pkgconf,exposed), where pkgconf is the
145         -- PackageConfig for the package containing the module, and
146         -- exposed is True if the package exposes that module.
147
148   -- The PackageIds of some known packages
149   basePackageId         :: PackageIdH,
150   rtsPackageId          :: PackageIdH,
151   haskell98PackageId    :: PackageIdH,
152   thPackageId           :: PackageIdH
153   }
154
155 data PackageIdH 
156    = HomePackage                -- The "home" package is the package curently
157                                 -- being compiled
158    | ExtPackage PackageId       -- An "external" package is any other package
159
160
161 isHomePackage :: PackageIdH -> Bool
162 isHomePackage HomePackage    = True
163 isHomePackage (ExtPackage _) = False
164
165 -- A PackageConfigMap maps a PackageId to a PackageConfig
166 type PackageConfigMap = UniqFM PackageConfig
167
168 emptyPackageConfigMap :: PackageConfigMap
169 emptyPackageConfigMap = emptyUFM
170
171 lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig
172 lookupPackage = lookupUFM
173
174 extendPackageConfigMap
175    :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap
176 extendPackageConfigMap pkg_map new_pkgs 
177   = foldl add pkg_map new_pkgs
178   where add pkg_map p = addToUFM pkg_map (packageConfigId p) p
179
180 getPackageDetails :: PackageState -> PackageId -> PackageConfig
181 getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkgIdMap dflags) ps)
182
183 -- ----------------------------------------------------------------------------
184 -- Loading the package config files and building up the package state
185
186 -- | Call this after parsing the DynFlags.  It reads the package
187 -- configuration files, and sets up various internal tables of package
188 -- information, according to the package-related flags on the
189 -- command-line (@-package@, @-hide-package@ etc.)
190 initPackages :: DynFlags -> IO DynFlags
191 initPackages dflags = do 
192   pkg_map <- readPackageConfigs dflags; 
193   state <- mkPackageState dflags pkg_map
194   return dflags{ pkgState = state }
195
196 -- -----------------------------------------------------------------------------
197 -- Reading the package database(s)
198
199 readPackageConfigs :: DynFlags -> IO PackageConfigMap
200 readPackageConfigs dflags = do
201         -- System one always comes first
202    system_pkgconf <- getPackageConfigPath
203    pkg_map1 <- readPackageConfig dflags emptyPackageConfigMap system_pkgconf
204
205         -- Read user's package conf (eg. ~/.ghc/i386-linux-6.3/package.conf)
206         -- unless the -no-user-package-conf flag was given.
207         -- We only do this when getAppUserDataDirectory is available 
208         -- (GHC >= 6.3).
209    (exists, pkgconf) <- catch (do
210       appdir <- getAppUserDataDirectory "ghc"
211       let 
212          pkgconf = appdir
213                    `joinFileName` (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion)
214                    `joinFileName` "package.conf"
215       flg <- doesFileExist pkgconf
216       return (flg, pkgconf))
217        -- gobble them all up and turn into False.
218       (\ _ -> return (False, ""))
219    pkg_map2 <- if (dopt Opt_ReadUserPackageConf dflags && exists)
220                   then readPackageConfig dflags pkg_map1 pkgconf
221                   else return pkg_map1
222
223         -- Read all the ones mentioned in -package-conf flags
224    pkg_map <- foldM (readPackageConfig dflags) pkg_map2
225                  (extraPkgConfs dflags)
226
227    return pkg_map
228
229
230 readPackageConfig
231    :: DynFlags -> PackageConfigMap -> FilePath -> IO PackageConfigMap
232 readPackageConfig dflags pkg_map conf_file = do
233   debugTraceMsg dflags 2 ("Using package config file: " ++ conf_file)
234   proto_pkg_configs <- loadPackageConfig conf_file
235   top_dir           <- getTopDir
236   let pkg_configs1 = mungePackagePaths top_dir proto_pkg_configs
237       pkg_configs2 = maybeHidePackages dflags pkg_configs1
238   return (extendPackageConfigMap pkg_map pkg_configs2)
239
240 maybeHidePackages :: DynFlags -> [PackageConfig] -> [PackageConfig]
241 maybeHidePackages dflags pkgs
242   | dopt Opt_HideAllPackages dflags = map hide pkgs
243   | otherwise                       = pkgs
244   where
245     hide pkg = pkg{ exposed = False }
246
247 mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig]
248 -- Replace the string "$topdir" at the beginning of a path
249 -- with the current topdir (obtained from the -B option).
250 mungePackagePaths top_dir ps = map munge_pkg ps
251  where 
252   munge_pkg p = p{ importDirs  = munge_paths (importDirs p),
253                    includeDirs = munge_paths (includeDirs p),
254                    libraryDirs = munge_paths (libraryDirs p),
255                    frameworkDirs = munge_paths (frameworkDirs p) }
256
257   munge_paths = map munge_path
258
259   munge_path p 
260           | Just p' <- maybePrefixMatch "$topdir" p = top_dir ++ p'
261           | otherwise                               = p
262
263
264 -- -----------------------------------------------------------------------------
265 -- When all the command-line options are in, we can process our package
266 -- settings and populate the package state.
267
268 mkPackageState :: DynFlags -> PackageConfigMap -> IO PackageState
269 mkPackageState dflags pkg_db = do
270   --
271   -- Modify the package database according to the command-line flags
272   -- (-package, -hide-package, -ignore-package, -hide-all-packages).
273   --
274   -- Also, here we build up a set of the packages mentioned in -package
275   -- flags on the command line; these are called the "explicit" packages.
276   -- we link these packages in eagerly.  The explicit set should contain
277   -- at least rts & base, which is why we pretend that the command line
278   -- contains -package rts & -package base.
279   --
280   let
281         flags = reverse (packageFlags dflags)
282
283         procflags pkgs expl [] = return (pkgs,expl)
284         procflags pkgs expl (ExposePackage str : flags) = do
285            case partition (matches str) pkgs of
286                 ([],_)   -> missingPackageErr str
287                 ([p],ps) -> procflags (p':ps) (addOneToUniqSet expl pkgid) flags
288                   where pkgid = packageConfigId p
289                         p' = p {exposed=True}
290                 (ps,_)   -> multiplePackagesErr str ps
291         procflags pkgs expl (HidePackage str : flags) = do
292            case partition (matches str) pkgs of
293                 ([],_)   -> missingPackageErr str
294                 ([p],ps) -> procflags (p':ps) expl flags
295                   where p' = p {exposed=False}
296                 (ps,_)   -> multiplePackagesErr str ps
297         procflags pkgs expl (IgnorePackage str : flags) = do
298            case partition (matches str) pkgs of
299                 (ps,qs) -> procflags qs expl flags
300                 -- missing package is not an error for -ignore-package,
301                 -- because a common usage is to -ignore-package P as
302                 -- a preventative measure just in case P exists.
303
304         -- A package named on the command line can either include the
305         -- version, or just the name if it is unambiguous.
306         matches str p
307                 =  str == showPackageId (package p)
308                 || str == pkgName (package p)
309   --
310   (pkgs1,explicit) <- procflags (eltsUFM pkg_db) emptyUniqSet flags
311   --
312   let
313         elimDanglingDeps pkgs = 
314            case partition (hasDanglingDeps pkgs) pkgs of
315               ([],ps) -> ps
316               (ps,qs) -> elimDanglingDeps qs
317
318         hasDanglingDeps pkgs p = any dangling (depends p)
319           where dangling pid = pid `notElem` all_pids
320                 all_pids = map package pkgs
321   --
322   -- Eliminate any packages which have dangling dependencies (perhaps
323   -- because the package was removed by -ignore-package).
324   --
325   let pkgs = elimDanglingDeps pkgs1
326       pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs
327   --
328   -- Find the transitive closure of dependencies of exposed
329   --
330   let exposed_pkgids = [ packageConfigId p | p <- pkgs, exposed p ]
331   dep_exposed <- closeDeps pkg_db exposed_pkgids
332   --
333   -- Look up some known PackageIds
334   --
335   let
336         lookupPackageByName :: FastString -> PackageIdH
337         lookupPackageByName nm = 
338           case [ conf | p <- dep_exposed,
339                         Just conf <- [lookupPackage pkg_db p],
340                         nm == mkFastString (pkgName (package conf)) ] of
341                 []     -> HomePackage
342                 (p:ps) -> ExtPackage (mkPackageId (package p))
343
344         -- Get the PackageIds for some known packages (we know the names,
345         -- but we don't know the versions).  Some of these packages might
346         -- not exist in the database, so they are Maybes.
347         basePackageId           = lookupPackageByName basePackageName
348         rtsPackageId            = lookupPackageByName rtsPackageName
349         haskell98PackageId      = lookupPackageByName haskell98PackageName
350         thPackageId             = lookupPackageByName thPackageName
351
352         -- add base & rts to the explicit packages
353         basicLinkedPackages = [basePackageId,rtsPackageId]
354         explicit' = addListToUniqSet explicit 
355                         [ p | ExtPackage p <- basicLinkedPackages ]
356   --
357   -- Close the explicit packages with their dependencies
358   --
359   dep_explicit <- closeDeps pkg_db (uniqSetToList explicit')
360   --
361   -- Build up a mapping from Module -> PackageConfig for all modules.
362   -- Discover any conflicts at the same time, and factor in the new exposed
363   -- status of each package.
364   --
365   let
366         extend_modmap modmap pkgname = do
367           let 
368                 pkg = expectJust "mkPackageState" (lookupPackage pkg_db pkgname)
369                 exposed_mods = map mkModule (exposedModules pkg)
370                 hidden_mods  = map mkModule (hiddenModules pkg)
371                 all_mods = exposed_mods ++ hidden_mods
372           --
373           -- check for overlaps
374           --
375           let
376                 overlaps = [ (m,pkg) | m <- all_mods, 
377                                        Just (pkg,_) <- [lookupUFM modmap m] ]
378           --
379           when (not (null overlaps)) $ overlappingError pkg overlaps
380           --
381           return (addListToUFM modmap 
382                     [(m, (pkg, m `elem` exposed_mods)) 
383                     | m <- all_mods])
384   --
385   mod_map <- foldM extend_modmap emptyUFM dep_exposed
386
387   return PackageState{ explicitPackages    = dep_explicit,
388                        pkgIdMap            = pkg_db,
389                        moduleToPkgConf     = mod_map,
390                        basePackageId       = basePackageId,
391                        rtsPackageId        = rtsPackageId,
392                        haskell98PackageId  = haskell98PackageId,
393                        thPackageId         = thPackageId
394                      }
395   -- done!
396
397 basePackageName      = FSLIT("base")
398 rtsPackageName       = FSLIT("rts")
399 haskell98PackageName = FSLIT("haskell98")
400 thPackageName        = FSLIT("template-haskell")
401                                 -- Template Haskell libraries in here
402
403 overlappingError pkg overlaps
404   = throwDyn (CmdLineError (showSDoc (vcat (map msg overlaps))))
405   where 
406         this_pkg = text (showPackageId (package pkg))
407         msg (mod,other_pkg) =
408            text "Error: module '" <> ppr mod
409                  <> text "' is exposed by package "
410                  <> this_pkg <> text " and package "
411                  <> text (showPackageId (package other_pkg))
412
413 multiplePackagesErr str ps =
414   throwDyn (CmdLineError (showSDoc (
415                    text "Error; multiple packages match" <+> 
416                         text str <> colon <+>
417                     sep (punctuate comma (map (text.showPackageId.package) ps))
418                 )))
419
420 -- -----------------------------------------------------------------------------
421 -- Extracting information from the packages in scope
422
423 -- Many of these functions take a list of packages: in those cases,
424 -- the list is expected to contain the "dependent packages",
425 -- i.e. those packages that were found to be depended on by the
426 -- current module/program.  These can be auto or non-auto packages, it
427 -- doesn't really matter.  The list is always combined with the list
428 -- of explicit (command-line) packages to determine which packages to
429 -- use.
430
431 getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String]
432 getPackageIncludePath dflags pkgs = do
433   ps <- getExplicitPackagesAnd dflags pkgs
434   return (nub (filter notNull (concatMap includeDirs ps)))
435
436         -- includes are in reverse dependency order (i.e. rts first)
437 getPackageCIncludes :: [PackageConfig] -> IO [String]
438 getPackageCIncludes pkg_configs = do
439   return (reverse (nub (filter notNull (concatMap includes pkg_configs))))
440
441 getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String]
442 getPackageLibraryPath dflags pkgs = do 
443   ps <- getExplicitPackagesAnd dflags pkgs
444   return (nub (filter notNull (concatMap libraryDirs ps)))
445
446 getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String]
447 getPackageLinkOpts dflags pkgs = do
448   ps <- getExplicitPackagesAnd dflags pkgs
449   let tag = buildTag dflags
450       rts_tag = rtsBuildTag dflags
451   let 
452         imp        = if opt_Static then "" else "_dyn"
453         libs p     = map ((++imp) . addSuffix) (hACK (hsLibraries p)) ++ extraLibraries p
454         all_opts p = map ("-l" ++) (libs p) ++ ldOptions p
455
456         suffix     = if null tag then "" else  '_':tag
457         rts_suffix = if null rts_tag then "" else  '_':rts_tag
458
459         addSuffix rts@"HSrts"    = rts       ++ rts_suffix
460         addSuffix other_lib      = other_lib ++ suffix
461
462   return (concat (map all_opts ps))
463   where
464
465      -- This is a totally horrible (temporary) hack, for Win32.  Problem is
466      -- that package.conf for Win32 says that the main prelude lib is 
467      -- split into HSbase1, HSbase2 and HSbase3, which is needed due to a bug
468      -- in the GNU linker (PEi386 backend). However, we still only
469      -- have HSbase.a for static linking, not HSbase{1,2,3}.a
470      -- getPackageLibraries is called to find the .a's to add to the static
471      -- link line.  On Win32, this hACK detects HSbase{1,2,3} and 
472      -- replaces them with HSbase, so static linking still works.
473      -- Libraries needed for dynamic (GHCi) linking are discovered via
474      -- different route (in InteractiveUI.linkPackage).
475      -- See driver/PackageSrc.hs for the HSbase1/HSbase2 split definition.
476      -- THIS IS A STRICTLY TEMPORARY HACK (famous last words ...)
477      -- JRS 04 Sept 01: Same appalling hack for HSwin32[1,2]
478      -- KAA 29 Mar  02: Same appalling hack for HSobjectio[1,2,3,4]
479      --
480      -- [sof 03/05: Renamed the (moribund) HSwin32 to HSwin_32 so as to
481      --  avoid filename conflicts with the 'Win32' package on a case-insensitive filesystem]
482      hACK libs
483 #      if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS)
484        = libs
485 #      else
486        = if   "HSbase1" `elem` libs && "HSbase2" `elem` libs && "HSbase3" `elem` libs
487          then "HSbase" : filter (not.(isPrefixOf "HSbase")) libs
488          else
489          if   "HSwin_321" `elem` libs && "HSwin_322" `elem` libs
490          then "HSwin_32" : filter (not.(isPrefixOf "HSwin_32")) libs
491          else 
492          if   "HSobjectio1" `elem` libs && "HSobjectio2" `elem` libs && "HSobjectio3" `elem` libs && "HSobjectio4" `elem` libs
493          then "HSobjectio" : filter (not.(isPrefixOf "HSobjectio")) libs
494          else 
495          libs
496 #      endif
497
498 getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String]
499 getPackageExtraCcOpts dflags pkgs = do
500   ps <- getExplicitPackagesAnd dflags pkgs
501   return (concatMap ccOptions ps)
502
503 getPackageFrameworkPath  :: DynFlags -> [PackageId] -> IO [String]
504 getPackageFrameworkPath dflags pkgs = do
505   ps <- getExplicitPackagesAnd dflags pkgs
506   return (nub (filter notNull (concatMap frameworkDirs ps)))
507
508 getPackageFrameworks  :: DynFlags -> [PackageId] -> IO [String]
509 getPackageFrameworks dflags pkgs = do
510   ps <- getExplicitPackagesAnd dflags pkgs
511   return (concatMap frameworks ps)
512
513 -- -----------------------------------------------------------------------------
514 -- Package Utils
515
516 -- Takes a Module, and if the module is in a package returns 
517 -- (pkgconf,exposed) where pkgconf is the PackageConfig for that package,
518 -- and exposed is True if the package exposes the module.
519 moduleToPackageConfig :: DynFlags -> Module -> Maybe (PackageConfig,Bool)
520 moduleToPackageConfig dflags m = 
521   lookupUFM (moduleToPkgConf (pkgState dflags)) m
522
523 isHomeModule :: DynFlags -> Module -> Bool
524 isHomeModule dflags mod = isNothing (moduleToPackageConfig dflags mod)
525
526 getExplicitPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig]
527 getExplicitPackagesAnd dflags pkgids =
528   let 
529       state   = pkgState dflags
530       pkg_map = pkgIdMap state
531       expl    = explicitPackages state
532   in do
533   all_pkgs <- foldM (add_package pkg_map) expl pkgids
534   return (map (getPackageDetails state) all_pkgs)
535
536 -- Takes a list of packages, and returns the list with dependencies included,
537 -- in reverse dependency order (a package appears before those it depends on).
538 closeDeps :: PackageConfigMap -> [PackageId] -> IO [PackageId]
539 closeDeps pkg_map ps = foldM (add_package pkg_map) [] ps
540
541 -- internal helper
542 add_package :: PackageConfigMap -> [PackageId] -> PackageId -> IO [PackageId]
543 add_package pkg_db ps p
544   | p `elem` ps = return ps     -- Check if we've already added this package
545   | otherwise =
546       case lookupPackage pkg_db p of
547         Nothing -> missingPackageErr (packageIdString p)
548         Just pkg -> do
549            -- Add the package's dependents also
550            let deps = map mkPackageId (depends pkg)
551            ps' <- foldM (add_package pkg_db) ps deps
552            return (p : ps')
553
554 missingPackageErr p =  throwDyn (CmdLineError ("unknown package: " ++ p))
555
556 -- -----------------------------------------------------------------------------
557 -- Determining whether a Name refers to something in another package or not.
558 -- Cross-package references need to be handled differently when dynamically-
559 -- linked libraries are involved.
560
561 isDllName :: DynFlags -> Name -> Bool
562 isDllName dflags name
563   | opt_Static = False
564   | otherwise =
565     case nameModule_maybe name of
566         Nothing -> False  -- no, it is not even an external name
567         Just mod ->
568             case lookupUFM (moduleToPkgConf (pkgState dflags)) mod of
569                 Just _  -> True   -- yes, its a package module
570                 Nothing -> False  -- no, must be a home module
571
572 -- -----------------------------------------------------------------------------
573 -- Displaying packages
574
575 dumpPackages :: DynFlags -> IO ()
576 -- Show package info on console, if verbosity is >= 3
577 dumpPackages dflags
578   = do  let pkg_map = pkgIdMap (pkgState dflags)
579         putMsg $ showSDoc $
580               vcat (map (text.showInstalledPackageInfo) (eltsUFM pkg_map))
581 \end{code}