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