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