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