Major patch to fix reporting of unused imports
[ghc-hetmet.git] / compiler / main / Packages.lhs
index 41a760a..505a797 100644 (file)
@@ -1,9 +1,8 @@
- %
-% (c) The University of Glasgow, 2006
 %
-% Package manipulation
+% (c) The University of Glasgow, 2006
 %
 \begin{code}
+-- | Package manipulation
 module Packages (
        module PackageConfig,
 
@@ -26,6 +25,9 @@ module Packages (
        getPackageFrameworks,
        getPreloadPackagesAnd,
 
+        collectIncludeDirs, collectLibraryPaths, collectLinkOpts,
+        packageHsLibs,
+
        -- * Utils
        isDllName
     )
@@ -48,48 +50,47 @@ import Outputable
 
 import System.Environment ( getEnv )
 import Distribution.InstalledPackageInfo hiding (depends)
-import Distribution.Package hiding (depends)
-import Distribution.Version
+import Distribution.Package hiding (depends, PackageId)
 import FastString
 import ErrUtils         ( debugTraceMsg, putMsg, Message )
+import Exception
 
 import System.Directory
 import System.FilePath
 import Data.Maybe
 import Control.Monad
 import Data.List
-import Control.Exception        ( throwDyn )
 
 -- ---------------------------------------------------------------------------
 -- The Package state
 
--- Package state is all stored in DynFlags, including the details of
+-- | Package state is all stored in 'DynFlag's, including the details of
 -- all packages, which packages are exposed, and which modules they
 -- provide.
-
--- The package state is computed by initPackages, and kept in DynFlags.
 --
---   * -package <pkg> causes <pkg> to become exposed, and all other packages 
+-- The package state is computed by 'initPackages', and kept in DynFlags.
+--
+--   * @-package <pkg>@ causes @<pkg>@ to become exposed, and all other packages 
 --     with the same name to become hidden.
 -- 
---   * -hide-package <pkg> causes <pkg> to become hidden.
+--   * @-hide-package <pkg>@ causes @<pkg>@ to become hidden.
 -- 
---   * Let exposedPackages be the set of packages thus exposed.  
---     Let depExposedPackages be the transitive closure from exposedPackages of
+--   * Let @exposedPackages@ be the set of packages thus exposed.  
+--     Let @depExposedPackages@ be the transitive closure from @exposedPackages@ of
 --     their dependencies.
 --
 --   * When searching for a module from an preload import declaration,
---     only the exposed modules in exposedPackages are valid.
+--     only the exposed modules in @exposedPackages@ are valid.
 --
 --   * When searching for a module from an implicit import, all modules
---     from depExposedPackages are valid.
+--     from @depExposedPackages@ are valid.
 --
---   * When linking in a comp manager mode, we link in packages the
+--   * When linking in a compilation manager mode, we link in packages the
 --     program depends on (the compiler knows this list by the
 --     time it gets to the link step).  Also, we link in all packages
---     which were mentioned with preload -package flags on the command-line,
---     or are a transitive dependency of same, or are "base"/"rts".
---     The reason for (b) is that we might need packages which don't
+--     which were mentioned with preload @-package@ flags on the command-line,
+--     or are a transitive dependency of same, or are \"base\"\/\"rts\".
+--     The reason for this is that we might need packages which don't
 --     contain any Haskell modules, and therefore won't be discovered
 --     by the normal mechanism of dependency tracking.
 
@@ -119,12 +120,13 @@ data PackageState = PackageState {
        -- exposed is True if the package exposes that module.
   }
 
--- A PackageConfigMap maps a PackageId to a PackageConfig
+-- | A PackageConfigMap maps a 'PackageId' to a 'PackageConfig'
 type PackageConfigMap = UniqFM PackageConfig
 
 emptyPackageConfigMap :: PackageConfigMap
 emptyPackageConfigMap = emptyUFM
 
+-- | Find the package we know about with the given id (e.g. \"foo-1.0\"), if any
 lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig
 lookupPackage = lookupUFM
 
@@ -134,8 +136,10 @@ extendPackageConfigMap pkg_map new_pkgs
   = foldl add pkg_map new_pkgs
   where add pkg_map p = addToUFM pkg_map (packageConfigId p) p
 
+-- | Looks up the package with the given id in the package state, panicing if it is
+-- not found
 getPackageDetails :: PackageState -> PackageId -> PackageConfig
-getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkgIdMap dflags) ps)
+getPackageDetails ps pid = expectJust "getPackageDetails" (lookupPackage (pkgIdMap ps) pid)
 
 -- ----------------------------------------------------------------------------
 -- Loading the package config files and building up the package state
@@ -147,11 +151,11 @@ getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkg
 --
 -- Returns a list of packages to link in if we're doing dynamic linking.
 -- This list contains the packages that the user explicitly mentioned with
--- -package flags.
+-- @-package@ flags.
 --
 -- 'initPackages' can be called again subsequently after updating the
 -- 'packageFlags' field of the 'DynFlags', and it will update the
--- 'packageState' in 'DynFlags' and return a list of packages to
+-- 'pkgState' in 'DynFlags' and return a list of packages to
 -- link in.
 initPackages :: DynFlags -> IO (DynFlags, [PackageId])
 initPackages dflags = do 
@@ -170,7 +174,7 @@ initPackages dflags = do
 
 readPackageConfigs :: DynFlags -> IO PackageConfigMap
 readPackageConfigs dflags = do
-   e_pkg_path <- try (getEnv "GHC_PACKAGE_PATH")
+   e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH")
    system_pkgconfs <- getSystemPackageConfigs dflags
 
    let pkgconfs = case e_pkg_path of
@@ -213,7 +217,7 @@ getSystemPackageConfigs dflags = do
        -- unless the -no-user-package-conf flag was given.
        -- We only do this when getAppUserDataDirectory is available 
        -- (GHC >= 6.3).
-   user_pkgconf <- handle (\_ -> return []) $ do
+   user_pkgconf <- do
       appdir <- getAppUserDataDirectory "ghc"
       let 
         pkgconf = appdir
@@ -223,6 +227,7 @@ getSystemPackageConfigs dflags = do
       if (flg && dopt Opt_ReadUserPackageConf dflags)
        then return [pkgconf]
        else return []
+    `catchIO` (\_ -> return [])
 
    return (user_pkgconf ++ system_pkgconfs ++ [system_pkgconf])
 
@@ -310,15 +315,16 @@ applyPackageFlag pkgs flag =
 matchingPackages :: String -> [PackageConfig]
          -> Maybe ([PackageConfig], [PackageConfig])
 matchingPackages str pkgs
-  = case partition (matches str) pkgs of
+  = case partition (packageMatches str) pkgs of
        ([],_)    -> Nothing
        (ps,rest) -> Just (sortByVersion ps, rest)
-  where
-        -- A package named on the command line can either include the
-       -- version, or just the name if it is unambiguous.
-       matches str p
-               =  str == display (package p)
-               || str == display (pkgName (package p))
+
+-- A package named on the command line can either include the
+-- version, or just the name if it is unambiguous.
+packageMatches :: String -> PackageConfig -> Bool
+packageMatches str p
+       =  str == display (package p)
+       || str == display (pkgName (package p))
 
 pickPackages :: [PackageConfig] -> [String] -> [PackageConfig]
 pickPackages pkgs strs = 
@@ -383,7 +389,8 @@ findWiredInPackages dflags pkgs preload this_package = do
                             (rtsPackageId, [""]),
                             (haskell98PackageId, [""]),
                             (thPackageId, [""]),
-                            (ndpPackageId, ["-seq", "-par"]) ]
+                            (dphSeqPackageId, [""]),
+                            (dphParPackageId, [""])]
 
         matches :: PackageConfig -> (PackageId, [String]) -> Bool
         pc `matches` (pid, suffixes)
@@ -404,11 +411,9 @@ findWiredInPackages dflags pkgs preload this_package = do
                           -> IO (Maybe (PackageIdentifier, PackageId))
        findWiredInPackage pkgs wired_pkg =
            let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ] in
-          case filter exposed all_ps of
-               [] -> case all_ps of
-                        []   -> notfound
-                        many -> pick (head (sortByVersion many))
-               many  -> pick (head (sortByVersion many))
+          case all_ps of
+               []   -> notfound
+               many -> pick (head (sortByVersion many))
           where
                 suffixes = snd wired_pkg
                 notfound = do
@@ -435,9 +440,18 @@ findWiredInPackages dflags pkgs preload this_package = do
   let 
         wired_in_ids = catMaybes mb_wired_in_ids
 
-       deleteOtherWiredInPackages pkgs = filterOut bad pkgs
-         where bad p = any (p `matches`) wired_in_pkgids
-                     && package p `notElem` map fst wired_in_ids
+        -- this is old: we used to assume that if there were
+        -- multiple versions of wired-in packages installed that
+        -- they were mutually exclusive.  Now we're assuming that
+        -- you have one "main" version of each wired-in package
+        -- (the latest version), and the others are backward-compat
+        -- wrappers that depend on this one.  e.g. base-4.0 is the
+        -- latest, base-3.0 is a compat wrapper depending on base-4.0.
+        {-
+       deleteOtherWiredInPackages pkgs = filterOut bad pkgs
+         where bad p = any (p `matches`) wired_in_pkgids
+                      && package p `notElem` map fst wired_in_ids
+        -}
 
        updateWiredInDependencies pkgs = map upd_pkg pkgs
          where upd_pkg p = p{ package = upd_pid (package p),
@@ -448,9 +462,9 @@ findWiredInPackages dflags pkgs preload this_package = do
                                ((x, y):_) -> x{ pkgName = PackageName (packageIdString y),
                                                  pkgVersion = Version [] [] }
 
-        pkgs1 = deleteOtherWiredInPackages pkgs
+        -- pkgs1 = deleteOtherWiredInPackages pkgs
 
-        pkgs2 = updateWiredInDependencies pkgs1
+        pkgs2 = updateWiredInDependencies pkgs
 
         preload1 = map upd_pid preload
 
@@ -545,8 +559,10 @@ mkPackageState dflags orig_pkg_db preload0 this_package = do
   let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs
 
       -- add base & rts to the preload packages
-      basicLinkedPackages = filter (flip elemUFM pkg_db)
-                                [basePackageId,rtsPackageId]
+      basicLinkedPackages
+       | dopt Opt_AutoLinkPackages dflags
+          = filter (flip elemUFM pkg_db) [basePackageId, rtsPackageId]
+       | otherwise = []
       -- but in any case remove the current package from the set of
       -- preloaded packages so that base/rts does not end up in the
       -- set up preloaded package when we are just building it
@@ -598,27 +614,41 @@ pprPkg p = text (display (package p))
 -- of preload (command-line) packages to determine which packages to
 -- use.
 
+-- | Find all the include directories in these and the preload packages
 getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String]
-getPackageIncludePath dflags pkgs = do
-  ps <- getPreloadPackagesAnd dflags pkgs
-  return (nub (filter notNull (concatMap includeDirs ps)))
+getPackageIncludePath dflags pkgs =
+  collectIncludeDirs `fmap` getPreloadPackagesAnd dflags pkgs
+
+collectIncludeDirs :: [PackageConfig] -> [FilePath] 
+collectIncludeDirs ps = nub (filter notNull (concatMap includeDirs ps))
 
+-- | Find all the library paths in these and the preload packages
 getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String]
-getPackageLibraryPath dflags pkgs = do 
-  ps <- getPreloadPackagesAnd dflags pkgs
-  return (nub (filter notNull (concatMap libraryDirs ps)))
+getPackageLibraryPath dflags pkgs =
+  collectLibraryPaths `fmap` getPreloadPackagesAnd dflags pkgs
+
+collectLibraryPaths :: [PackageConfig] -> [FilePath]
+collectLibraryPaths ps = nub (filter notNull (concatMap libraryDirs ps))
 
+-- | Find all the link options in these and the preload packages
 getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String]
-getPackageLinkOpts dflags pkgs = do
-  ps <- getPreloadPackagesAnd dflags pkgs
-  let tag = buildTag dflags
-      rts_tag = rtsBuildTag dflags
-  let 
+getPackageLinkOpts dflags pkgs = 
+  collectLinkOpts dflags `fmap` getPreloadPackagesAnd dflags pkgs
+
+collectLinkOpts :: DynFlags -> [PackageConfig] -> [String]
+collectLinkOpts dflags ps = concat (map all_opts ps)
+  where
+       libs p     = packageHsLibs dflags p ++ extraLibraries p
+       all_opts p = map ("-l" ++) (libs p) ++ ldOptions p
+
+packageHsLibs :: DynFlags -> PackageConfig -> [String]
+packageHsLibs dflags p = map (mkDynName . addSuffix) (hsLibraries p)
+  where
+        tag = buildTag dflags
+        rts_tag = rtsBuildTag dflags
+
        mkDynName | opt_Static = id
                  | otherwise = (++ ("-ghc" ++ cProjectVersion))
-       libs p     = map (mkDynName . addSuffix) (hsLibraries p)
-                        ++ extraLibraries p
-       all_opts p = map ("-l" ++) (libs p) ++ ldOptions p
 
         addSuffix rts@"HSrts"    = rts       ++ (expandTag rts_tag)
         addSuffix other_lib      = other_lib ++ (expandTag tag)
@@ -626,18 +656,19 @@ getPackageLinkOpts dflags pkgs = do
         expandTag t | null t = ""
                    | otherwise = '_':t
 
-  return (concat (map all_opts ps))
-
+-- | Find all the C-compiler options in these and the preload packages
 getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String]
 getPackageExtraCcOpts dflags pkgs = do
   ps <- getPreloadPackagesAnd dflags pkgs
   return (concatMap ccOptions ps)
 
+-- | Find all the package framework paths in these and the preload packages
 getPackageFrameworkPath  :: DynFlags -> [PackageId] -> IO [String]
 getPackageFrameworkPath dflags pkgs = do
   ps <- getPreloadPackagesAnd dflags pkgs
   return (nub (filter notNull (concatMap frameworkDirs ps)))
 
+-- | Find all the package frameworks in these and the preload packages
 getPackageFrameworks  :: DynFlags -> [PackageId] -> IO [String]
 getPackageFrameworks dflags pkgs = do
   ps <- getPreloadPackagesAnd dflags pkgs
@@ -646,15 +677,17 @@ getPackageFrameworks dflags pkgs = do
 -- -----------------------------------------------------------------------------
 -- Package Utils
 
--- | Takes a Module, and if the module is in a package returns 
--- @(pkgconf,exposed)@ where pkgconf is the PackageConfig for that package,
--- and exposed is True if the package exposes the module.
+-- | Takes a 'Module', and if the module is in a package returns 
+-- @(pkgconf, exposed)@ where pkgconf is the PackageConfig for that package,
+-- and exposed is @True@ if the package exposes the module.
 lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(PackageConfig,Bool)]
 lookupModuleInAllPackages dflags m =
   case lookupUFM (moduleToPkgConfAll (pkgState dflags)) m of
        Nothing -> []
        Just ps -> ps
 
+-- | Find all the 'PackageConfig' in both the preload packages from 'DynFlags' and corresponding to the list of
+-- 'PackageConfig's
 getPreloadPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig]
 getPreloadPackagesAnd dflags pkgids =
   let 
@@ -674,7 +707,7 @@ closeDeps pkg_map ps = throwErr (closeDepsErr pkg_map ps)
 
 throwErr :: MaybeErr Message a -> IO a
 throwErr m = case m of
-               Failed e    -> throwDyn (CmdLineError (showSDoc e))
+               Failed e    -> ghcError (CmdLineError (showSDoc e))
                Succeeded r -> return r
 
 closeDepsErr :: PackageConfigMap -> [(PackageId,Maybe PackageId)]
@@ -697,7 +730,7 @@ add_package pkg_db ps (p, mb_parent)
           return (p : ps')
 
 missingPackageErr :: String -> IO [PackageConfig]
-missingPackageErr p = throwDyn (CmdLineError (showSDoc (missingPackageMsg p)))
+missingPackageErr p = ghcError (CmdLineError (showSDoc (missingPackageMsg p)))
 
 missingPackageMsg :: String -> SDoc
 missingPackageMsg p = ptext (sLit "unknown package:") <+> text p
@@ -709,6 +742,7 @@ missingDependencyMsg (Just parent)
 
 -- -----------------------------------------------------------------------------
 
+-- | Will the 'Name' come from a dynamically linked library?
 isDllName :: PackageId -> Name -> Bool
 isDllName this_pkg name
   | opt_Static = False
@@ -718,15 +752,12 @@ isDllName this_pkg name
 -- -----------------------------------------------------------------------------
 -- Displaying packages
 
+-- | Show package info on console, if verbosity is >= 3
 dumpPackages :: DynFlags -> IO ()
--- Show package info on console, if verbosity is >= 3
 dumpPackages dflags
   = do  let pkg_map = pkgIdMap (pkgState dflags)
        putMsg dflags $
-             vcat (map (text.showInstalledPackageInfo.to_ipi) (eltsUFM pkg_map))
- where
-  to_ipi pkgconf@(InstalledPackageInfo { exposedModules = e,
-                                         hiddenModules = h }) = 
-    pkgconf{ exposedModules = map moduleNameString e,
-             hiddenModules  = map moduleNameString h }
+              vcat (map (text . showInstalledPackageInfo
+                              . packageConfigToInstalledPackageInfo)
+                        (eltsUFM pkg_map))
 \end{code}