[commit: ghc] wip/remove-cabal-dep: Address a number of Edward's code review comments (e1d9fcd)
git at git.haskell.org
git at git.haskell.org
Sun Aug 24 22:47:51 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/remove-cabal-dep
Link : http://ghc.haskell.org/trac/ghc/changeset/e1d9fcdef97d4787b22870f7e876e655aa28d945/ghc
>---------------------------------------------------------------
commit e1d9fcdef97d4787b22870f7e876e655aa28d945
Author: Duncan Coutts <duncan at well-typed.com>
Date: Sun Aug 24 23:43:40 2014 +0100
Address a number of Edward's code review comments
Some others addressed as part of other recent patches.
>---------------------------------------------------------------
e1d9fcdef97d4787b22870f7e876e655aa28d945
compiler/main/Finder.lhs | 1 +
libraries/bin-package-db/GHC/PackageDb.hs | 7 +++++++
utils/ghc-pkg/Main.hs | 17 +++++++++++------
3 files changed, 19 insertions(+), 6 deletions(-)
diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs
index 65151d9..b5ad08b 100644
--- a/compiler/main/Finder.lhs
+++ b/compiler/main/Finder.lhs
@@ -615,6 +615,7 @@ cantFindErr cannot_find _ dflags mod_name find_result
| otherwise =
hang (ptext (sLit "Locations searched:")) 2 $ vcat (map text files)
+ pkg_hidden :: PackageKey -> SDoc
pkg_hidden pkgid =
ptext (sLit "It is a member of the hidden package")
<+> quotes (ppr pkgid)
diff --git a/libraries/bin-package-db/GHC/PackageDb.hs b/libraries/bin-package-db/GHC/PackageDb.hs
index eea525c..5039a01 100644
--- a/libraries/bin-package-db/GHC/PackageDb.hs
+++ b/libraries/bin-package-db/GHC/PackageDb.hs
@@ -154,6 +154,10 @@ readPackageDbForGhc file =
-- | Read the part of the package DB that ghc-pkg is interested in
--
+-- Note that the Binary instance for ghc-pkg's representation of packages
+-- is not defined in this package. This is because ghc-pkg uses Cabal types
+-- (and Binary instances for these) which this package does not depend on.
+--
readPackageDbForGhcPkg :: Binary pkgs => FilePath -> IO pkgs
readPackageDbForGhcPkg file =
decodeFromFile file getDbForGhcPkg
@@ -224,6 +228,9 @@ headerMagic :: BS.ByteString
headerMagic = BS.Char8.pack "\0ghcpkg\0"
+-- TODO: we may be able to replace the following with utils from the binary
+-- package in future.
+
-- | Feed a 'Get' decoder with data chunks from a file.
--
decodeFromFile :: FilePath -> Get a -> IO a
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
index ec23eb4..fdb255a 100644
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -590,8 +590,9 @@ getPkgDatabases verbosity modify use_user use_cache expand_vars my_flags = do
Just f -> return (Just (f, True))
fs -> return (Just (last fs, True))
- -- If the user database exists, and for "check" and all "modify" commands
- -- we will attempt to use the user db.
+ -- If the user database exists, and for "use_user" commands (which includes
+ -- "ghc-pkg check" and all commands that modify the db) we will attempt to
+ -- use the user db.
let sys_databases
| Just (user_conf,user_exists) <- mb_user_conf,
use_user || user_exists = [user_conf, global_conf]
@@ -694,8 +695,7 @@ readParseDatabase verbosity mb_user_conf modify use_cache path
e_tcache <- tryIO $ getModificationTime cache
case e_tcache of
Left ex -> do
- when ( verbosity > Normal
- || verbosity >= Normal && not modify) $
+ whenReportCacheErrors $
if isDoesNotExistError ex
then do
warn ("WARNING: cache does not exist: " ++ cache)
@@ -727,8 +727,7 @@ readParseDatabase verbosity mb_user_conf modify use_cache path
pkgs <- GhcPkg.readPackageDbForGhcPkg cache
mkPackageDB pkgs
else do
- when ( verbosity > Normal
- || verbosity >= Normal && not modify) $ do
+ whenReportCacheErrors $ do
warn ("WARNING: cache is out of date: " ++ cache)
warn ("ghc will see an old view of this " ++
"package db. Use 'ghc-pkg recache' to fix.")
@@ -741,6 +740,12 @@ readParseDatabase verbosity mb_user_conf modify use_cache path
parseSingletonPackageConf verbosity f
pkgs <- mapM doFile $ map (path </>) confs
mkPackageDB pkgs
+
+ -- We normally report cache errors for read-only commands,
+ -- since modify commands because will usually fix the cache.
+ whenReportCacheErrors =
+ when ( verbosity > Normal
+ || verbosity >= Normal && not modify)
where
mkPackageDB pkgs = do
path_abs <- absolutePath path
More information about the ghc-commits
mailing list