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