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