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