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