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