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