85cf4ac55beac63960da2447739b106f94a26024
[ghc-hetmet.git] / ghc / compiler / main / Packages.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section{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         PackageIdH(..), isHomePackage,
16         PackageState(..), 
17         initPackages,
18         getPackageDetails,
19         checkForPackageConflicts,
20         lookupModuleInAllPackages,
21
22         HomeModules, mkHomeModules, isHomeModule,
23
24         -- * Inspecting the set of packages in scope
25         getPackageIncludePath,
26         getPackageCIncludes,
27         getPackageLibraryPath,
28         getPackageLinkOpts,
29         getPackageExtraCcOpts,
30         getPackageFrameworkPath,
31         getPackageFrameworks,
32         getExplicitPackagesAnd,
33
34         -- * Utils
35         isDllName
36     )
37 where
38
39 #include "HsVersions.h"
40
41 import PackageConfig    
42 import SysTools         ( getTopDir, getPackageConfigPath )
43 import ParsePkgConf     ( loadPackageConfig )
44 import DynFlags         ( dopt, DynFlag(..), DynFlags(..), PackageFlag(..) )
45 import StaticFlags      ( opt_Static )
46 import Config           ( cProjectVersion )
47 import Name             ( Name, nameModule_maybe )
48 import UniqFM
49 import Module
50 import FiniteMap
51 import UniqSet
52 import Util
53 import Maybes           ( expectJust, MaybeErr(..) )
54 import Panic
55 import Outputable
56
57 #if __GLASGOW_HASKELL__ >= 603
58 import System.Directory ( getAppUserDataDirectory )
59 #else
60 import Compat.Directory ( getAppUserDataDirectory )
61 #endif
62
63 import Distribution.InstalledPackageInfo
64 import Distribution.Package
65 import Distribution.Version
66 import Data.Maybe       ( isNothing )
67 import System.Directory ( doesFileExist )
68 import Control.Monad    ( foldM )
69 import Data.List        ( nub, partition, sortBy )
70
71 #ifdef mingw32_TARGET_OS
72 import Data.List        ( isPrefixOf )
73 #endif
74 import Data.List        ( isSuffixOf )
75
76 import FastString
77 import EXCEPTION        ( throwDyn )
78 import ErrUtils         ( debugTraceMsg, putMsg, Message )
79
80 -- ---------------------------------------------------------------------------
81 -- The Package state
82
83 -- Package state is all stored in DynFlags, including the details of
84 -- all packages, which packages are exposed, and which modules they
85 -- provide.
86
87 -- The package state is computed by initPackages, and kept in DynFlags.
88 --
89 --   * -package <pkg> causes <pkg> to become exposed, and all other packages 
90 --      with the same name to become hidden.
91 -- 
92 --   * -hide-package <pkg> causes <pkg> to become hidden.
93 -- 
94 --   * Let exposedPackages be the set of packages thus exposed.  
95 --     Let depExposedPackages be the transitive closure from exposedPackages of
96 --     their dependencies.
97 --
98 --   * It is an error for any two packages in depExposedPackages to provide the
99 --     same module.
100 -- 
101 --   * When searching for a module from an explicit import declaration,
102 --     only the exposed modules in exposedPackages are valid.
103 --
104 --   * When searching for a module from an implicit import, all modules
105 --     from depExposedPackages are valid.
106 --
107 --   * When linking in a comp manager mode, we link in packages the
108 --     program depends on (the compiler knows this list by the
109 --     time it gets to the link step).  Also, we link in all packages
110 --     which were mentioned with explicit -package flags on the command-line,
111 --     or are a transitive dependency of same, or are "base"/"rts".
112 --     The reason for (b) is that we might need packages which don't
113 --     contain any Haskell modules, and therefore won't be discovered
114 --     by the normal mechanism of dependency tracking.
115
116
117 -- One important thing that the package state provides is a way to
118 -- tell, for a given module, whether it is part of the current package
119 -- or not.  We need to know this for two reasons:
120 --
121 --  * generating cross-DLL calls is different from intra-DLL calls 
122 --    (see below).
123 --  * we don't record version information in interface files for entities
124 --    in a different package.
125 -- 
126 -- Notes on DLLs
127 -- ~~~~~~~~~~~~~
128 -- When compiling module A, which imports module B, we need to 
129 -- know whether B will be in the same DLL as A.  
130 --      If it's in the same DLL, we refer to B_f_closure
131 --      If it isn't, we refer to _imp__B_f_closure
132 -- When compiling A, we record in B's Module value whether it's
133 -- in a different DLL, by setting the DLL flag.
134
135 data PackageState = PackageState {
136
137   explicitPackages      :: [PackageId],
138         -- The packages we're going to link in eagerly.  This list
139         -- should be in reverse dependency order; that is, a package
140         -- is always mentioned before the packages it depends on.
141
142   origPkgIdMap          :: PackageConfigMap, -- PackageId   -> PackageConfig
143         -- the full package database
144
145   pkgIdMap              :: PackageConfigMap, -- PackageId   -> PackageConfig
146         -- Derived from origPkgIdMap.
147         -- The exposed flags are adjusted according to -package and
148         -- -hide-package flags, and -ignore-package removes packages.
149
150   moduleToPkgConfAll    :: ModuleEnv [(PackageConfig,Bool)],
151         -- Derived from pkgIdMap.       
152         -- Maps Module to (pkgconf,exposed), where pkgconf is the
153         -- PackageConfig for the package containing the module, and
154         -- exposed is True if the package exposes that module.
155
156   -- The PackageIds of some known packages
157   basePackageId         :: PackageIdH,
158   rtsPackageId          :: PackageIdH,
159   haskell98PackageId    :: PackageIdH,
160   thPackageId           :: PackageIdH
161   }
162
163 data PackageIdH 
164    = HomePackage                -- The "home" package is the package curently
165                                 -- being compiled
166    | ExtPackage PackageId       -- An "external" package is any other package
167
168
169 isHomePackage :: PackageIdH -> Bool
170 isHomePackage HomePackage    = True
171 isHomePackage (ExtPackage _) = False
172
173 -- A PackageConfigMap maps a PackageId to a PackageConfig
174 type PackageConfigMap = UniqFM PackageConfig
175
176 emptyPackageConfigMap :: PackageConfigMap
177 emptyPackageConfigMap = emptyUFM
178
179 lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig
180 lookupPackage = lookupUFM
181
182 extendPackageConfigMap
183    :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap
184 extendPackageConfigMap pkg_map new_pkgs 
185   = foldl add pkg_map new_pkgs
186   where add pkg_map p = addToUFM pkg_map (packageConfigId p) p
187
188 getPackageDetails :: PackageState -> PackageId -> PackageConfig
189 getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkgIdMap dflags) ps)
190
191 -- ----------------------------------------------------------------------------
192 -- Loading the package config files and building up the package state
193
194 -- | Call this after parsing the DynFlags.  It reads the package
195 -- configuration files, and sets up various internal tables of package
196 -- information, according to the package-related flags on the
197 -- command-line (@-package@, @-hide-package@ etc.)
198 initPackages :: DynFlags -> IO DynFlags
199 initPackages dflags = do 
200   pkg_map <- readPackageConfigs dflags; 
201   state <- mkPackageState dflags pkg_map
202   return dflags{ pkgState = state }
203
204 -- -----------------------------------------------------------------------------
205 -- Reading the package database(s)
206
207 readPackageConfigs :: DynFlags -> IO PackageConfigMap
208 readPackageConfigs dflags = do
209         -- System one always comes first
210    system_pkgconf <- getPackageConfigPath
211    pkg_map1 <- readPackageConfig dflags emptyPackageConfigMap system_pkgconf
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    (exists, pkgconf) <- catch (do
218       appdir <- getAppUserDataDirectory "ghc"
219       let 
220          pkgconf = appdir
221                    `joinFileName` (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion)
222                    `joinFileName` "package.conf"
223       flg <- doesFileExist pkgconf
224       return (flg, pkgconf))
225        -- gobble them all up and turn into False.
226       (\ _ -> return (False, ""))
227    pkg_map2 <- if (dopt Opt_ReadUserPackageConf dflags && exists)
228                   then readPackageConfig dflags pkg_map1 pkgconf
229                   else return pkg_map1
230
231         -- Read all the ones mentioned in -package-conf flags
232    pkg_map <- foldM (readPackageConfig dflags) pkg_map2
233                  (extraPkgConfs dflags)
234
235    return pkg_map
236
237
238 readPackageConfig
239    :: DynFlags -> PackageConfigMap -> FilePath -> IO PackageConfigMap
240 readPackageConfig dflags pkg_map conf_file = do
241   debugTraceMsg dflags 2 ("Using package config file: " ++ conf_file)
242   proto_pkg_configs <- loadPackageConfig conf_file
243   top_dir           <- getTopDir
244   let pkg_configs1 = mungePackagePaths top_dir proto_pkg_configs
245       pkg_configs2 = maybeHidePackages dflags pkg_configs1
246   return (extendPackageConfigMap pkg_map pkg_configs2)
247
248 maybeHidePackages :: DynFlags -> [PackageConfig] -> [PackageConfig]
249 maybeHidePackages dflags pkgs
250   | dopt Opt_HideAllPackages dflags = map hide pkgs
251   | otherwise                       = pkgs
252   where
253     hide pkg = pkg{ exposed = False }
254
255 mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig]
256 -- Replace the string "$topdir" at the beginning of a path
257 -- with the current topdir (obtained from the -B option).
258 mungePackagePaths top_dir ps = map munge_pkg ps
259  where 
260   munge_pkg p = p{ importDirs  = munge_paths (importDirs p),
261                    includeDirs = munge_paths (includeDirs p),
262                    libraryDirs = munge_paths (libraryDirs p),
263                    frameworkDirs = munge_paths (frameworkDirs p) }
264
265   munge_paths = map munge_path
266
267   munge_path p 
268           | Just p' <- maybePrefixMatch "$topdir" p = top_dir ++ p'
269           | otherwise                               = p
270
271
272 -- -----------------------------------------------------------------------------
273 -- When all the command-line options are in, we can process our package
274 -- settings and populate the package state.
275
276 mkPackageState :: DynFlags -> PackageConfigMap -> IO PackageState
277 mkPackageState dflags orig_pkg_db = do
278   --
279   -- Modify the package database according to the command-line flags
280   -- (-package, -hide-package, -ignore-package, -hide-all-packages).
281   --
282   -- Also, here we build up a set of the packages mentioned in -package
283   -- flags on the command line; these are called the "explicit" packages.
284   -- we link these packages in eagerly.  The explicit set should contain
285   -- at least rts & base, which is why we pretend that the command line
286   -- contains -package rts & -package base.
287   --
288   let
289         flags = reverse (packageFlags dflags)
290
291         procflags pkgs expl [] = return (pkgs,expl)
292         procflags pkgs expl (ExposePackage str : flags) = do
293            case pick str pkgs of
294                 Nothing -> missingPackageErr str
295                 Just (p,ps) -> procflags (p':ps') expl' flags
296                   where pkgid = packageConfigId p
297                         p' = p {exposed=True}
298                         ps' = hideAll (pkgName (package p)) ps
299                         expl' = addOneToUniqSet expl pkgid
300         procflags pkgs expl (HidePackage str : flags) = do
301            case partition (matches str) pkgs of
302                 ([],_)   -> missingPackageErr str
303                 (ps,qs) -> procflags (map hide ps ++ qs) expl flags
304                   where hide p = p {exposed=False}
305         procflags pkgs expl (IgnorePackage str : flags) = do
306            case partition (matches str) pkgs of
307                 (ps,qs) -> procflags qs expl flags
308                 -- missing package is not an error for -ignore-package,
309                 -- because a common usage is to -ignore-package P as
310                 -- a preventative measure just in case P exists.
311
312         pick str pkgs
313           = case partition (matches str) pkgs of
314                 ([],_) -> Nothing
315                 (ps,rest) -> 
316                    case sortBy (flip (comparing (pkgVersion.package))) ps of
317                         (p:ps) -> Just (p, ps ++ rest)
318                         _ -> panic "Packages.pick"
319
320         comparing f a b = f a `compare` f b
321
322         -- A package named on the command line can either include the
323         -- version, or just the name if it is unambiguous.
324         matches str p
325                 =  str == showPackageId (package p)
326                 || str == pkgName (package p)
327
328         -- When a package is requested to be exposed, we hide all other
329         -- packages with the same name.
330         hideAll name ps = map maybe_hide ps
331           where maybe_hide p | pkgName (package p) == name = p {exposed=False}
332                              | otherwise                   = p
333   --
334   (pkgs1,explicit) <- procflags (eltsUFM orig_pkg_db) emptyUniqSet flags
335   --
336   -- hide all packages for which there is also a later version
337   -- that is already exposed.  This just makes it non-fatal to have two
338   -- versions of a package exposed, which can happen if you install a
339   -- later version of a package in the user database, for example.
340   --
341   let maybe_hide p
342            | not (exposed p) = return p
343            | (p' : _) <- later_versions = do
344                 debugTraceMsg dflags 2 $
345                    ("hiding package " ++ showPackageId (package p) ++
346                     " to avoid conflict with later version " ++
347                     showPackageId (package p'))
348                 return (p {exposed=False})
349            | otherwise = return p
350           where myname = pkgName (package p)
351                 myversion = pkgVersion (package p)
352                 later_versions = [ p | p <- pkgs1, exposed p,
353                                     let pkg = package p,
354                                     pkgName pkg == myname,
355                                     pkgVersion pkg > myversion ]
356                 a_later_version_is_exposed
357                   = not (null later_versions)
358
359   pkgs2 <- mapM maybe_hide pkgs1
360   --
361   -- Eliminate any packages which have dangling dependencies (perhaps
362   -- because the package was removed by -ignore-package).
363   --
364   let
365         elimDanglingDeps pkgs = 
366            case partition (not.null.snd) (map (getDanglingDeps pkgs) pkgs) of
367               ([],ps) -> return (map fst ps)
368               (ps,qs) -> do
369                  mapM_ reportElim ps
370                  elimDanglingDeps (map fst qs)
371
372         reportElim (p, deps) = 
373                 debugTraceMsg dflags 2 $ showSDoc $
374                    (ptext SLIT("package") <+> pprPkg p <+> 
375                         ptext SLIT("will be ignored due to missing dependencies:") $$ 
376                     nest 2 (hsep (map (text.showPackageId) deps)))
377
378         getDanglingDeps pkgs p = (p, filter dangling (depends p))
379           where dangling pid = pid `notElem` all_pids
380                 all_pids = map package pkgs
381   --
382   pkgs <- elimDanglingDeps pkgs2
383   let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs
384   --
385   -- Find the transitive closure of dependencies of exposed
386   --
387   let exposed_pkgids = [ packageConfigId p | p <- pkgs, exposed p ]
388   dep_exposed <- closeDeps pkg_db exposed_pkgids
389   --
390   -- Look up some known PackageIds
391   --
392   let
393         lookupPackageByName :: FastString -> PackageIdH
394         lookupPackageByName nm = 
395           case [ conf | p <- dep_exposed,
396                         Just conf <- [lookupPackage pkg_db p],
397                         nm == mkFastString (pkgName (package conf)) ] of
398                 []     -> HomePackage
399                 (p:ps) -> ExtPackage (mkPackageId (package p))
400
401         -- Get the PackageIds for some known packages (we know the names,
402         -- but we don't know the versions).  Some of these packages might
403         -- not exist in the database, so they are Maybes.
404         basePackageId           = lookupPackageByName basePackageName
405         rtsPackageId            = lookupPackageByName rtsPackageName
406         haskell98PackageId      = lookupPackageByName haskell98PackageName
407         thPackageId             = lookupPackageByName thPackageName
408
409         -- add base & rts to the explicit packages
410         basicLinkedPackages = [basePackageId,rtsPackageId]
411         explicit' = addListToUniqSet explicit 
412                         [ p | ExtPackage p <- basicLinkedPackages ]
413   --
414   -- Close the explicit packages with their dependencies
415   --
416   dep_explicit <- closeDeps pkg_db (uniqSetToList explicit')
417   --
418   -- Build up a mapping from Module -> PackageConfig for all modules.
419   -- Discover any conflicts at the same time, and factor in the new exposed
420   -- status of each package.
421   --
422   let mod_map = mkModuleMap pkg_db dep_exposed
423
424   return PackageState{ explicitPackages     = dep_explicit,
425                        origPkgIdMap         = orig_pkg_db,
426                        pkgIdMap             = pkg_db,
427                        moduleToPkgConfAll   = mod_map,
428                        basePackageId        = basePackageId,
429                        rtsPackageId         = rtsPackageId,
430                        haskell98PackageId   = haskell98PackageId,
431                        thPackageId          = thPackageId
432                      }
433   -- done!
434
435 basePackageName      = FSLIT("base")
436 rtsPackageName       = FSLIT("rts")
437 haskell98PackageName = FSLIT("haskell98")
438 thPackageName        = FSLIT("template-haskell")
439                                 -- Template Haskell libraries in here
440
441 mkModuleMap
442   :: PackageConfigMap
443   -> [PackageId]
444   -> ModuleEnv [(PackageConfig, Bool)]
445 mkModuleMap pkg_db pkgs = foldr extend_modmap emptyUFM pkgs
446   where
447         extend_modmap pkgname modmap =
448                 addListToUFM_C (++) modmap 
449                     [(m, [(pkg, m `elem` exposed_mods)]) | m <- all_mods]
450           where
451                 pkg = expectJust "mkModuleMap" (lookupPackage pkg_db pkgname)
452                 exposed_mods = map mkModule (exposedModules pkg)
453                 hidden_mods  = map mkModule (hiddenModules pkg)
454                 all_mods = exposed_mods ++ hidden_mods
455
456 -- -----------------------------------------------------------------------------
457 -- Check for conflicts in the program.
458
459 -- | A conflict arises if the program contains two modules with the same
460 -- name, which can arise if the program depends on multiple packages that
461 -- expose the same module, or if the program depends on a package that
462 -- contains a module also present in the program (the "home package").
463 --
464 checkForPackageConflicts
465    :: DynFlags
466    -> [Module]          -- modules in the home package
467    -> [PackageId]       -- packages on which the program depends
468    -> MaybeErr Message ()
469
470 checkForPackageConflicts dflags mods pkgs = do
471     let 
472         state   = pkgState dflags
473         pkg_db  = pkgIdMap state
474     --
475     dep_pkgs <- closeDepsErr pkg_db pkgs
476
477     let 
478         extend_modmap pkgname modmap  =
479                 addListToFM_C (++) modmap
480                     [(m, [(pkg, m `elem` exposed_mods)]) | m <- all_mods]
481           where
482                 pkg = expectJust "checkForPackageConflicts" 
483                                 (lookupPackage pkg_db pkgname)
484                 exposed_mods = map mkModule (exposedModules pkg)
485                 hidden_mods  = map mkModule (hiddenModules pkg)
486                 all_mods = exposed_mods ++ hidden_mods
487
488         mod_map = foldr extend_modmap emptyFM pkgs
489         mod_map_list :: [(Module,[(PackageConfig,Bool)])]
490         mod_map_list = fmToList mod_map
491
492         overlaps = [ (m, map fst ps) | (m,ps@(_:_:_)) <- mod_map_list ]
493     --
494     if not (null overlaps)
495         then Failed (pkgOverlapError overlaps)
496         else do
497
498     let 
499         overlap_mods = [ (mod,pkg)
500                        | mod <- mods,
501                          Just ((pkg,_):_) <- [lookupFM mod_map mod] ]    
502                                 -- will be only one package here
503     if not (null overlap_mods)
504         then Failed (modOverlapError overlap_mods)
505         else do
506
507     return ()
508        
509 pkgOverlapError overlaps =  vcat (map msg overlaps)
510   where 
511         msg (mod,pkgs) =
512            text "conflict: module" <+> quotes (ppr mod)
513                  <+> ptext SLIT("is present in multiple packages:")
514                  <+> hsep (punctuate comma (map pprPkg pkgs))
515
516 modOverlapError overlaps =   vcat (map msg overlaps)
517   where 
518         msg (mod,pkg) = fsep [
519                 text "conflict: module",
520                 quotes (ppr mod),
521                 ptext SLIT("belongs to the current program/library"),
522                 ptext SLIT("and also to package"),
523                 pprPkg pkg ]
524
525 pprPkg :: PackageConfig -> SDoc
526 pprPkg p = text (showPackageId (package p))
527
528 -- -----------------------------------------------------------------------------
529 -- Extracting information from the packages in scope
530
531 -- Many of these functions take a list of packages: in those cases,
532 -- the list is expected to contain the "dependent packages",
533 -- i.e. those packages that were found to be depended on by the
534 -- current module/program.  These can be auto or non-auto packages, it
535 -- doesn't really matter.  The list is always combined with the list
536 -- of explicit (command-line) packages to determine which packages to
537 -- use.
538
539 getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String]
540 getPackageIncludePath dflags pkgs = do
541   ps <- getExplicitPackagesAnd dflags pkgs
542   return (nub (filter notNull (concatMap includeDirs ps)))
543
544         -- includes are in reverse dependency order (i.e. rts first)
545 getPackageCIncludes :: [PackageConfig] -> IO [String]
546 getPackageCIncludes pkg_configs = do
547   return (reverse (nub (filter notNull (concatMap includes pkg_configs))))
548
549 getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String]
550 getPackageLibraryPath dflags pkgs = do 
551   ps <- getExplicitPackagesAnd dflags pkgs
552   return (nub (filter notNull (concatMap libraryDirs ps)))
553
554 getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String]
555 getPackageLinkOpts dflags pkgs = do
556   ps <- getExplicitPackagesAnd dflags pkgs
557   let tag = buildTag dflags
558       rts_tag = rtsBuildTag dflags
559   let 
560         imp        = if opt_Static then "" else "_dyn"
561         libs p     = map ((++imp) . addSuffix) (hACK (hsLibraries p))
562                          ++ hACK_dyn (extraLibraries p)
563         all_opts p = map ("-l" ++) (libs p) ++ ldOptions p
564
565         suffix     = if null tag then "" else  '_':tag
566         rts_suffix = if null rts_tag then "" else  '_':rts_tag
567
568         addSuffix rts@"HSrts"    = rts       ++ rts_suffix
569         addSuffix other_lib      = other_lib ++ suffix
570
571         -- This is a hack that's even more horrible (and hopefully more temporary)
572         -- than the one below. HSbase_cbits and friends require the _dyn suffix
573         -- for dynamic linking, but not _p or other 'way' suffix. So we just add
574         -- _dyn to extraLibraries if they already have a _cbits suffix.
575         
576         hACK_dyn = map hack
577           where hack lib | not opt_Static && "_cbits" `isSuffixOf` lib = lib ++ "_dyn"
578                          | otherwise = lib
579
580   return (concat (map all_opts ps))
581   where
582
583      -- This is a totally horrible (temporary) hack, for Win32.  Problem is
584      -- that package.conf for Win32 says that the main prelude lib is 
585      -- split into HSbase1, HSbase2 and HSbase3, which is needed due to a bug
586      -- in the GNU linker (PEi386 backend). However, we still only
587      -- have HSbase.a for static linking, not HSbase{1,2,3}.a
588      -- getPackageLibraries is called to find the .a's to add to the static
589      -- link line.  On Win32, this hACK detects HSbase{1,2,3} and 
590      -- replaces them with HSbase, so static linking still works.
591      -- Libraries needed for dynamic (GHCi) linking are discovered via
592      -- different route (in InteractiveUI.linkPackage).
593      -- See driver/PackageSrc.hs for the HSbase1/HSbase2 split definition.
594      -- THIS IS A STRICTLY TEMPORARY HACK (famous last words ...)
595      -- JRS 04 Sept 01: Same appalling hack for HSwin32[1,2]
596      -- KAA 29 Mar  02: Same appalling hack for HSobjectio[1,2,3,4]
597      --
598      -- [sof 03/05: Renamed the (moribund) HSwin32 to HSwin_32 so as to
599      --  avoid filename conflicts with the 'Win32' package on a case-insensitive filesystem]
600      hACK libs
601 #      if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS)
602        = libs
603 #      else
604        = if   "HSbase1" `elem` libs && "HSbase2" `elem` libs && "HSbase3" `elem` libs
605          then "HSbase" : filter (not.(isPrefixOf "HSbase")) libs
606          else
607          if   "HSwin_321" `elem` libs && "HSwin_322" `elem` libs
608          then "HSwin_32" : filter (not.(isPrefixOf "HSwin_32")) libs
609          else 
610          if   "HSobjectio1" `elem` libs && "HSobjectio2" `elem` libs && "HSobjectio3" `elem` libs && "HSobjectio4" `elem` libs
611          then "HSobjectio" : filter (not.(isPrefixOf "HSobjectio")) libs
612          else 
613          libs
614 #      endif
615
616
617 getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String]
618 getPackageExtraCcOpts dflags pkgs = do
619   ps <- getExplicitPackagesAnd dflags pkgs
620   return (concatMap ccOptions ps)
621
622 getPackageFrameworkPath  :: DynFlags -> [PackageId] -> IO [String]
623 getPackageFrameworkPath dflags pkgs = do
624   ps <- getExplicitPackagesAnd dflags pkgs
625   return (nub (filter notNull (concatMap frameworkDirs ps)))
626
627 getPackageFrameworks  :: DynFlags -> [PackageId] -> IO [String]
628 getPackageFrameworks dflags pkgs = do
629   ps <- getExplicitPackagesAnd dflags pkgs
630   return (concatMap frameworks ps)
631
632 -- -----------------------------------------------------------------------------
633 -- Package Utils
634
635 -- | Takes a Module, and if the module is in a package returns 
636 -- @(pkgconf,exposed)@ where pkgconf is the PackageConfig for that package,
637 -- and exposed is True if the package exposes the module.
638 lookupModuleInAllPackages :: DynFlags -> Module -> [(PackageConfig,Bool)]
639 lookupModuleInAllPackages dflags m =
640   case lookupModuleEnv (moduleToPkgConfAll (pkgState dflags)) m of
641         Nothing -> []
642         Just ps -> ps
643
644 getExplicitPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig]
645 getExplicitPackagesAnd dflags pkgids =
646   let 
647       state   = pkgState dflags
648       pkg_map = pkgIdMap state
649       expl    = explicitPackages state
650   in do
651   all_pkgs <- throwErr (foldM (add_package pkg_map) expl pkgids)
652   return (map (getPackageDetails state) all_pkgs)
653
654 -- Takes a list of packages, and returns the list with dependencies included,
655 -- in reverse dependency order (a package appears before those it depends on).
656 closeDeps :: PackageConfigMap -> [PackageId] -> IO [PackageId]
657 closeDeps pkg_map ps = throwErr (closeDepsErr pkg_map ps)
658
659 throwErr :: MaybeErr Message a -> IO a
660 throwErr m = case m of
661                 Failed e    -> throwDyn (CmdLineError (showSDoc e))
662                 Succeeded r -> return r
663
664 closeDepsErr :: PackageConfigMap -> [PackageId]
665         -> MaybeErr Message [PackageId]
666 closeDepsErr pkg_map ps = foldM (add_package pkg_map) [] ps
667
668 -- internal helper
669 add_package :: PackageConfigMap -> [PackageId] -> PackageId 
670         -> MaybeErr Message [PackageId]
671 add_package pkg_db ps p
672   | p `elem` ps = return ps     -- Check if we've already added this package
673   | otherwise =
674       case lookupPackage pkg_db p of
675         Nothing -> Failed (missingPackageMsg (packageIdString p))
676         Just pkg -> do
677            -- Add the package's dependents also
678            let deps = map mkPackageId (depends pkg)
679            ps' <- foldM (add_package pkg_db) ps deps
680            return (p : ps')
681
682 missingPackageErr p = throwDyn (CmdLineError (showSDoc (missingPackageMsg p)))
683 missingPackageMsg p = ptext SLIT("unknown package:") <+> text p
684
685 -- -----------------------------------------------------------------------------
686 -- The home module set
687
688 newtype HomeModules = HomeModules ModuleSet
689
690 mkHomeModules :: [Module] -> HomeModules
691 mkHomeModules = HomeModules . mkModuleSet
692
693 isHomeModule :: HomeModules -> Module -> Bool
694 isHomeModule (HomeModules set) mod  = elemModuleSet mod set
695
696 -- Determining whether a Name refers to something in another package or not.
697 -- Cross-package references need to be handled differently when dynamically-
698 -- linked libraries are involved.
699
700 isDllName :: HomeModules -> Name -> Bool
701 isDllName pdeps name
702   | opt_Static = False
703   | Just mod <- nameModule_maybe name = not (isHomeModule pdeps mod)
704   | otherwise = False  -- no, it is not even an external name
705
706 -- -----------------------------------------------------------------------------
707 -- Displaying packages
708
709 dumpPackages :: DynFlags -> IO ()
710 -- Show package info on console, if verbosity is >= 3
711 dumpPackages dflags
712   = do  let pkg_map = pkgIdMap (pkgState dflags)
713         putMsg $ showSDoc $
714               vcat (map (text.showInstalledPackageInfo) (eltsUFM pkg_map))
715 \end{code}