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