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