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