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