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