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