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