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