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