[project @ 2004-11-30 16:07:01 by simonmar]
[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         PackageState(..),
16         initPackages,
17         moduleToPackageConfig,
18         getPackageDetails,
19         isHomeModule,
20
21         -- * Inspecting the set of packages in scope
22         getPackageIncludePath,
23         getPackageCIncludes,
24         getPackageLibraryPath,
25         getPackageLinkOpts,
26         getPackageExtraCcOpts,
27         getPackageFrameworkPath,
28         getPackageFrameworks,
29         getExplicitPackagesAnd,
30
31         -- * Utils
32         isDllName
33     )
34 where
35
36 #include "HsVersions.h"
37
38 import PackageConfig    
39 import DriverState      ( v_Build_tag, v_RTS_Build_tag, v_Static )
40 import SysTools         ( getTopDir, getPackageConfigPath )
41 import ParsePkgConf     ( loadPackageConfig )
42 import CmdLineOpts      ( DynFlags(..), PackageFlag(..), verbosity,
43                           opt_Static )
44 import Config           ( cTARGETARCH, cTARGETOS, cProjectVersion )
45 import Name             ( Name, nameModule_maybe )
46 import Module           ( Module, mkModule )
47 import UniqFM
48 import UniqSet
49 import Util
50 import Panic
51 import Outputable
52
53 #if __GLASGOW_HASKELL__ >= 603
54 import System.Directory ( getAppUserDataDirectory )
55 #else
56 import Compat.Directory ( getAppUserDataDirectory )
57 #endif
58
59 import Distribution.InstalledPackageInfo
60 import Distribution.Package
61 import Distribution.Version
62 import System.IO        ( hPutStrLn, stderr )
63 import Data.Maybe       ( fromJust, isNothing )
64 import System.Directory ( doesFileExist )
65 import Control.Monad    ( when, foldM )
66 import Data.List        ( nub, partition )
67 import FastString
68 import DATA_IOREF
69 import EXCEPTION        ( throwDyn )
70
71 -- ---------------------------------------------------------------------------
72 -- The Package state
73
74 -- Package state is all stored in DynFlags, including the details of
75 -- all packages, which packages are exposed, and which modules they
76 -- provide.
77
78 -- The package state is computed by initPackages, and kept in DynFlags.
79 --
80 --   * -package <pkg> causes <pkg> to become exposed, and all other packages 
81 --      with the same name to become hidden.
82 -- 
83 --   * -hide-package <pkg> causes <pkg> to become hidden.
84 -- 
85 --   * Let exposedPackages be the set of packages thus exposed.  
86 --     Let depExposedPackages be the transitive closure from exposedPackages of
87 --     their dependencies.
88 --
89 --   * It is an error for any two packages in depExposedPackages to provide the
90 --     same module.
91 -- 
92 --   * When searching for a module from an explicit import declaration,
93 --     only the exposed modules in exposedPackages are valid.
94 --
95 --   * When searching for a module from an implicit import, all modules
96 --     from depExposedPackages are valid.
97 --
98 --   * When linking in a comp manager mode, we link in packages the
99 --     program depends on (the compiler knows this list by the
100 --     time it gets to the link step).  Also, we link in all packages
101 --     which were mentioned with explicit -package flags on the command-line,
102 --     or are a transitive dependency of same, or are "base"/"rts".
103 --     The reason for (b) is that we might need packages which don't
104 --     contain any Haskell modules, and therefore won't be discovered
105 --     by the normal mechanism of dependency tracking.
106
107
108 -- One important thing that the package state provides is a way to
109 -- tell, for a given module, whether it is part of the current package
110 -- or not.  We need to know this for two reasons:
111 --
112 --  * generating cross-DLL calls is different from intra-DLL calls 
113 --    (see below).
114 --  * we don't record version information in interface files for entities
115 --    in a different package.
116 -- 
117 -- Notes on DLLs
118 -- ~~~~~~~~~~~~~
119 -- When compiling module A, which imports module B, we need to 
120 -- know whether B will be in the same DLL as A.  
121 --      If it's in the same DLL, we refer to B_f_closure
122 --      If it isn't, we refer to _imp__B_f_closure
123 -- When compiling A, we record in B's Module value whether it's
124 -- in a different DLL, by setting the DLL flag.
125
126 data PackageState = PackageState {
127
128   explicitPackages      :: [PackageId],
129         -- The packages we're going to link in eagerly.  This list
130         -- should be in reverse dependency order; that is, a package
131         -- is always mentioned before the packages it depends on.
132
133   pkgIdMap              :: PackageConfigMap, -- PackageId   -> PackageConfig
134         -- mapping derived from the package databases and
135         -- command-line package flags.
136
137   moduleToPkgConf       :: UniqFM (PackageConfig,Bool),
138         -- Maps Module to (pkgconf,exposed), where pkgconf is the
139         -- PackageConfig for the package containing the module, and
140         -- exposed is True if the package exposes that module.
141
142   -- The PackageIds of some known packages
143   basePackageId         :: Maybe PackageId,
144   rtsPackageId          :: Maybe PackageId,
145   haskell98PackageId    :: Maybe PackageId,
146   thPackageId           :: Maybe PackageId
147   }
148
149 -- A PackageConfigMap maps a PackageId to a PackageConfig
150 type PackageConfigMap = UniqFM PackageConfig
151
152 emptyPackageConfigMap :: PackageConfigMap
153 emptyPackageConfigMap = emptyUFM
154
155 lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig
156 lookupPackage = lookupUFM
157
158 extendPackageConfigMap
159    :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap
160 extendPackageConfigMap pkg_map new_pkgs 
161   = foldl add pkg_map new_pkgs
162   where add pkg_map p = addToUFM pkg_map (packageConfigId p) p
163
164 getPackageDetails :: PackageState -> PackageId -> PackageConfig
165 getPackageDetails dflags ps = fromJust (lookupPackage (pkgIdMap dflags) ps)
166
167 -- ----------------------------------------------------------------------------
168 -- Loading the package config files and building up the package state
169
170 initPackages :: DynFlags -> IO DynFlags
171 initPackages dflags = do 
172   pkg_map <- readPackageConfigs dflags; 
173   state <- mkPackageState dflags pkg_map
174   return dflags{ pkgState = state }
175
176 -- -----------------------------------------------------------------------------
177 -- Reading the package database(s)
178
179 readPackageConfigs :: DynFlags -> IO PackageConfigMap
180 readPackageConfigs dflags = do
181         -- System one always comes first
182    system_pkgconf <- getPackageConfigPath
183    pkg_map1 <- readPackageConfig dflags emptyPackageConfigMap system_pkgconf
184
185         -- Read user's package conf (eg. ~/.ghc/i386-linux-6.3/package.conf)
186         -- unless the -no-user-package-conf flag was given.
187         -- We only do this when getAppUserDataDirectory is available 
188         -- (GHC >= 6.3).
189    appdir <- getAppUserDataDirectory "ghc"
190    let 
191          pkgconf = appdir ++ '/':cTARGETARCH ++ '-':cTARGETOS
192                         ++ '-':cProjectVersion ++ "/package.conf"
193    --
194    exists <- doesFileExist pkgconf
195    pkg_map2 <- if (readUserPkgConf dflags && exists)
196                   then readPackageConfig dflags pkg_map1 pkgconf
197                   else return pkg_map1
198
199         -- Read all the ones mentioned in -package-conf flags
200    pkg_map <- foldM (readPackageConfig dflags) pkg_map2
201                  (extraPkgConfs dflags)
202
203    return pkg_map
204
205
206 readPackageConfig
207    :: DynFlags -> PackageConfigMap -> FilePath -> IO PackageConfigMap
208 readPackageConfig dflags pkg_map conf_file = do
209   when (verbosity dflags >= 2) $
210         hPutStrLn stderr ("Reading package config file: "
211                          ++ conf_file)
212   proto_pkg_configs <- loadPackageConfig conf_file
213   top_dir           <- getTopDir
214   let pkg_configs = mungePackagePaths top_dir proto_pkg_configs
215   return (extendPackageConfigMap pkg_map pkg_configs)
216
217
218 mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig]
219 -- Replace the string "$libdir" at the beginning of a path
220 -- with the current libdir (obtained from the -B option).
221 mungePackagePaths top_dir ps = map munge_pkg ps
222  where 
223   munge_pkg p = p{ importDirs  = munge_paths (importDirs p),
224                    includeDirs = munge_paths (includeDirs p),
225                    libraryDirs = munge_paths (libraryDirs p),
226                    frameworkDirs = munge_paths (frameworkDirs p) }
227
228   munge_paths = map munge_path
229
230   munge_path p 
231           | Just p' <- maybePrefixMatch "$libdir" p = top_dir ++ p'
232           | otherwise                               = p
233
234
235 -- -----------------------------------------------------------------------------
236 -- When all the command-line options are in, we can process our package
237 -- settings and populate the package state.
238
239 mkPackageState :: DynFlags -> PackageConfigMap -> IO PackageState
240 mkPackageState dflags pkg_db = do
241   --
242   -- Modify the package database according to the command-line flags
243   -- (-package, -hide-package, -ignore-package).
244   --
245   -- Also, here we build up a set of the packages mentioned in -package
246   -- flags on the command line; these are called the "explicit" packages.
247   -- we link these packages in eagerly.  The explicit set should contain
248   -- at least rts & base, which is why we pretend that the command line
249   -- contains -package rts & -package base.
250   --
251   let
252         flags = reverse (packageFlags dflags)
253
254         procflags pkgs expl [] = return (pkgs,expl)
255         procflags pkgs expl (ExposePackage str : flags) = do
256            case partition (matches str) pkgs of
257                 ([],_)   -> missingPackageErr str
258                 ([p],ps) -> procflags (p':ps) (addOneToUniqSet expl pkgid) flags
259                   where pkgid = packageConfigId p
260                         p' = p {exposed=True}
261                 (ps,_)   -> multiplePackagesErr str ps
262         procflags pkgs expl (HidePackage str : flags) = do
263            case partition (matches str) pkgs of
264                 ([],_)   -> missingPackageErr str
265                 ([p],ps) -> procflags (p':ps) expl flags
266                   where p' = p {exposed=False}
267                 (ps,_)   -> multiplePackagesErr str ps
268         procflags pkgs expl (IgnorePackage str : flags) = do
269            case partition (matches str) pkgs of
270                 (ps,qs) -> procflags qs expl flags
271                 -- missing package is not an error for -ignore-package,
272                 -- because a common usage is to -ignore-package P as
273                 -- a preventative measure just in case P exists.
274
275         -- A package named on the command line can either include the
276         -- version, or just the name if it is unambiguous.
277         matches str p
278                 =  str == showPackageId (package p)
279                 || str == pkgName (package p)
280   --
281   (pkgs1,explicit) <- procflags (eltsUFM pkg_db) emptyUniqSet flags
282   --
283   let
284         elimDanglingDeps pkgs = 
285            case partition (hasDanglingDeps pkgs) pkgs of
286               ([],ps) -> ps
287               (ps,qs) -> elimDanglingDeps qs
288
289         hasDanglingDeps pkgs p = any dangling (depends p)
290           where dangling pid = pid `notElem` all_pids
291                 all_pids = map package pkgs
292   --
293   -- Eliminate any packages which have dangling dependencies (perhaps
294   -- because the package was removed by -ignore-package).
295   --
296   let pkgs = elimDanglingDeps pkgs1
297       pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs
298   --
299   -- Find the transitive closure of dependencies of exposed
300   --
301   let exposed_pkgids = [ packageConfigId p | p <- pkgs, exposed p ]
302   dep_exposed <- closeDeps pkg_db exposed_pkgids
303   --
304   -- Look up some known PackageIds
305   --
306   let
307         lookupPackageByName nm = 
308           case [ conf | p <- dep_exposed,
309                         Just conf <- [lookupPackage pkg_db p],
310                         nm == mkFastString (pkgName (package conf)) ] of
311                 []     -> Nothing
312                 (p:ps) -> Just (mkPackageId (package p))
313
314         -- Get the PackageIds for some known packages (we know the names,
315         -- but we don't know the versions).  Some of these packages might
316         -- not exist in the database, so they are Maybes.
317         basePackageId           = lookupPackageByName basePackageName
318         rtsPackageId            = lookupPackageByName rtsPackageName
319         haskell98PackageId      = lookupPackageByName haskell98PackageName
320         thPackageId             = lookupPackageByName thPackageName
321
322         -- add base & rts to the explicit packages
323         basicLinkedPackages = [basePackageId,rtsPackageId]
324         explicit' = addListToUniqSet explicit 
325                         [ p | Just p <- basicLinkedPackages ]
326   --
327   -- Close the explicit packages with their dependencies
328   --
329   dep_explicit <- closeDeps pkg_db (uniqSetToList explicit')
330   --
331   -- Build up a mapping from Module -> PackageConfig for all modules.
332   -- Discover any conflicts at the same time, and factor in the new exposed
333   -- status of each package.
334   --
335   let
336         extend_modmap modmap pkgname = do
337           let 
338                 pkg = fromJust (lookupPackage pkg_db pkgname)
339                 exposed_mods = map mkModule (exposedModules pkg)
340                 hidden_mods  = map mkModule (hiddenModules pkg)
341                 all_mods = exposed_mods ++ hidden_mods
342           --
343           -- check for overlaps
344           --
345           let
346                 overlaps = [ (m,pkg) | m <- all_mods, 
347                                        Just (pkg,_) <- [lookupUFM modmap m] ]
348           --
349           when (not (null overlaps)) $ overlappingError pkg overlaps
350           --
351           let
352           return (addListToUFM modmap 
353                     [(m, (pkg, m `elem` exposed_mods)) 
354                     | m <- all_mods])
355   --
356   mod_map <- foldM extend_modmap emptyUFM dep_exposed
357
358   return PackageState{ explicitPackages    = dep_explicit,
359                        pkgIdMap            = pkg_db,
360                        moduleToPkgConf     = mod_map,
361                        basePackageId       = basePackageId,
362                        rtsPackageId        = rtsPackageId,
363                        haskell98PackageId  = haskell98PackageId,
364                        thPackageId         = thPackageId
365                      }
366   -- done!
367
368 basePackageName      = FSLIT("base")
369 rtsPackageName       = FSLIT("rts")
370 haskell98PackageName = FSLIT("haskell98")
371 thPackageName        = FSLIT("template-haskell")
372                                 -- Template Haskell libraries in here
373
374 overlappingError pkg overlaps
375   = throwDyn (CmdLineError (showSDoc (vcat (map msg overlaps))))
376   where 
377         this_pkg = text (showPackageId (package pkg))
378         msg (mod,other_pkg) =
379            text "Error: module '" <> ppr mod
380                  <> text "' is exposed by package "
381                  <> this_pkg <> text " and package "
382                  <> text (showPackageId (package other_pkg))
383
384 multiplePackagesErr str ps =
385   throwDyn (CmdLineError (showSDoc (
386                    text "Error; multiple packages match" <+> 
387                         text str <> colon <+>
388                     sep (punctuate comma (map (text.showPackageId.package) ps))
389                 )))
390
391 -- -----------------------------------------------------------------------------
392 -- Extracting information from the packages in scope
393
394 -- Many of these functions take a list of packages: in those cases,
395 -- the list is expected to contain the "dependent packages",
396 -- i.e. those packages that were found to be depended on by the
397 -- current module/program.  These can be auto or non-auto packages, it
398 -- doesn't really matter.  The list is always combined with the list
399 -- of explicit (command-line) packages to determine which packages to
400 -- use.
401
402 getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String]
403 getPackageIncludePath dflags pkgs = do
404   ps <- getExplicitPackagesAnd dflags pkgs
405   return (nub (filter notNull (concatMap includeDirs ps)))
406
407         -- includes are in reverse dependency order (i.e. rts first)
408 getPackageCIncludes :: [PackageConfig] -> IO [String]
409 getPackageCIncludes pkg_configs = do
410   return (reverse (nub (filter notNull (concatMap includes pkg_configs))))
411
412 getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String]
413 getPackageLibraryPath dflags pkgs = do 
414   ps <- getExplicitPackagesAnd dflags pkgs
415   return (nub (filter notNull (concatMap libraryDirs ps)))
416
417 getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String]
418 getPackageLinkOpts dflags pkgs = do
419   ps <- getExplicitPackagesAnd dflags pkgs
420   tag <- readIORef v_Build_tag
421   rts_tag <- readIORef v_RTS_Build_tag
422   static <- readIORef v_Static
423   let 
424         imp        = if static then "" else "_imp"
425         libs p     = map addSuffix (hACK (hsLibraries p)) ++ extraLibraries p
426         imp_libs p = map (++imp) (libs p)
427         all_opts p = map ("-l" ++) (imp_libs p) ++ extraLdOpts p
428
429         suffix     = if null tag then "" else  '_':tag
430         rts_suffix = if null rts_tag then "" else  '_':rts_tag
431
432         addSuffix rts@"HSrts"    = rts       ++ rts_suffix
433         addSuffix other_lib      = other_lib ++ suffix
434
435   return (concat (map all_opts ps))
436   where
437
438      -- This is a totally horrible (temporary) hack, for Win32.  Problem is
439      -- that package.conf for Win32 says that the main prelude lib is 
440      -- split into HSbase1, HSbase2 and HSbase3, which is needed due to a bug
441      -- in the GNU linker (PEi386 backend). However, we still only
442      -- have HSbase.a for static linking, not HSbase{1,2,3}.a
443      -- getPackageLibraries is called to find the .a's to add to the static
444      -- link line.  On Win32, this hACK detects HSbase{1,2,3} and 
445      -- replaces them with HSbase, so static linking still works.
446      -- Libraries needed for dynamic (GHCi) linking are discovered via
447      -- different route (in InteractiveUI.linkPackage).
448      -- See driver/PackageSrc.hs for the HSbase1/HSbase2 split definition.
449      -- THIS IS A STRICTLY TEMPORARY HACK (famous last words ...)
450      -- JRS 04 Sept 01: Same appalling hack for HSwin32[1,2]
451      -- KAA 29 Mar  02: Same appalling hack for HSobjectio[1,2,3,4]
452      hACK libs
453 #      if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS)
454        = libs
455 #      else
456        = if   "HSbase1" `elem` libs && "HSbase2" `elem` libs && "HSbase3" `elem` libs
457          then "HSbase" : filter (not.(isPrefixOf "HSbase")) libs
458          else
459          if   "HSwin321" `elem` libs && "HSwin322" `elem` libs
460          then "HSwin32" : filter (not.(isPrefixOf "HSwin32")) libs
461          else 
462          if   "HSobjectio1" `elem` libs && "HSobjectio2" `elem` libs && "HSobjectio3" `elem` libs && "HSobjectio4" `elem` libs
463          then "HSobjectio" : filter (not.(isPrefixOf "HSobjectio")) libs
464          else 
465          libs
466 #      endif
467
468 getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String]
469 getPackageExtraCcOpts dflags pkgs = do
470   ps <- getExplicitPackagesAnd dflags pkgs
471   return (concatMap extraCcOpts ps)
472
473 getPackageFrameworkPath  :: DynFlags -> [PackageId] -> IO [String]
474 getPackageFrameworkPath dflags pkgs = do
475   ps <- getExplicitPackagesAnd dflags pkgs
476   return (nub (filter notNull (concatMap frameworkDirs ps)))
477
478 getPackageFrameworks  :: DynFlags -> [PackageId] -> IO [String]
479 getPackageFrameworks dflags pkgs = do
480   ps <- getExplicitPackagesAnd dflags pkgs
481   return (concatMap extraFrameworks ps)
482
483 -- -----------------------------------------------------------------------------
484 -- Package Utils
485
486 -- Takes a Module, and if the module is in a package returns 
487 -- (pkgconf,exposed) where pkgconf is the PackageConfig for that package,
488 -- and exposed is True if the package exposes the module.
489 moduleToPackageConfig :: DynFlags -> Module -> Maybe (PackageConfig,Bool)
490 moduleToPackageConfig dflags m = 
491   lookupUFM (moduleToPkgConf (pkgState dflags)) m
492
493 isHomeModule :: DynFlags -> Module -> Bool
494 isHomeModule dflags mod = isNothing (moduleToPackageConfig dflags mod)
495
496 getExplicitPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig]
497 getExplicitPackagesAnd dflags pkgids =
498   let 
499       state   = pkgState dflags
500       pkg_map = pkgIdMap state
501       expl    = explicitPackages state
502   in do
503   all_pkgs <- foldM (add_package pkg_map) expl pkgids
504   return (map (getPackageDetails state) all_pkgs)
505
506 -- Takes a list of packages, and returns the list with dependencies included,
507 -- in reverse dependency order (a package appears before those it depends on).
508 closeDeps :: PackageConfigMap -> [PackageId] -> IO [PackageId]
509 closeDeps pkg_map ps = foldM (add_package pkg_map) [] ps
510
511 -- internal helper
512 add_package :: PackageConfigMap -> [PackageId] -> PackageId -> IO [PackageId]
513 add_package pkg_db ps p
514   | p `elem` ps = return ps     -- Check if we've already added this package
515   | otherwise =
516       case lookupPackage pkg_db p of
517         Nothing -> missingPackageErr (packageIdString p)
518         Just pkg -> do
519            -- Add the package's dependents also
520            let deps = map mkPackageId (depends pkg)
521            ps' <- foldM (add_package pkg_db) ps deps
522            return (p : ps')
523
524 missingPackageErr p =  throwDyn (CmdLineError ("unknown package: " ++ p))
525
526 -- -----------------------------------------------------------------------------
527 -- Determining whether a Name refers to something in another package or not.
528 -- Cross-package references need to be handled differently when dynamically-
529 -- linked libraries are involved.
530
531 isDllName :: DynFlags -> Name -> Bool
532 isDllName dflags name
533   | opt_Static = False
534   | otherwise =
535     case nameModule_maybe name of
536         Nothing -> False  -- no, it is not even an external name
537         Just mod ->
538             case lookupUFM (moduleToPkgConf (pkgState dflags)) mod of
539                 Just _  -> True   -- yes, its a package module
540                 Nothing -> False  -- no, must be a home module
541
542 -- -----------------------------------------------------------------------------
543 -- Displaying packages
544
545 dumpPackages :: DynFlags -> IO ()
546 -- Show package info on console, if verbosity is >= 3
547 dumpPackages dflags
548   = do  let pkg_map = pkgIdMap (pkgState dflags)
549         hPutStrLn stderr $ showSDoc $
550               vcat (map (text.showInstalledPackageInfo) (eltsUFM pkg_map))
551 \end{code}