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