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