[GHC] #13354: Package database locking patch broke ghc-pkg with non-existent database

GHC ghc-devs at haskell.org
Wed Mar 1 03:36:21 UTC 2017


#13354: Package database locking patch broke ghc-pkg with non-existent database
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:  8.2.1
       Component:  Package system    |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by arybczak):

 Ehh, it's a bit tricky. In theory the following fix should do it:

 {{{#!diff
 --- a/utils/ghc-pkg/Main.hs
 +++ b/utils/ghc-pkg/Main.hs
 @@ -807,7 +807,10 @@ readParseDatabase :: forall mode t. Verbosity
  readParseDatabase verbosity mb_user_conf mode use_cache path
    -- the user database (only) is allowed to be non-existent
    | Just (user_conf,False) <- mb_user_conf, path == user_conf
 -  = mkPackageDB [] =<< F.mapM (const $ GhcPkg.lockPackageDb path) mode
 +  = do lock <- F.forM mode $ \_ -> do
 +         createDirectoryIfMissing True path
 +         GhcPkg.lockPackageDb cache
 +       mkPackageDB [] lock
    | otherwise
    = do e <- tryIO $ getDirectoryContents path
         case e of
 @@ -828,7 +831,6 @@ readParseDatabase verbosity mb_user_conf mode
 use_cache path
           Right fs
             | not use_cache -> ignore_cache (const $ return ())
             | otherwise -> do
 -              let cache = path </> cachefilename
                tdir     <- getModificationTime path
                e_tcache <- tryIO $ getModificationTime cache
                case e_tcache of
 @@ -888,6 +890,8 @@ readParseDatabase verbosity mb_user_conf mode
 use_cache path
                   whenReportCacheErrors = when $ verbosity > Normal
                     || verbosity >= Normal && GhcPkg.isDbOpenReadMode mode
    where
 +    cache = path </> cachefilename
 +
      recacheAdvice
        | Just (user_conf, True) <- mb_user_conf, path == user_conf
        = "Use 'ghc-pkg recache --user' to fix."
 }}}

 So if we open user database in read/write mode and it doesn't exist,
 create the missing directory so that we can create a lock file.

 However, this clashes with the way we try to open a database that contains
 a specific package for modification: we open in read write mode and if it
 doesn't contain given package, we "downgrade" to read only by releasing a
 lock. So in this case we'll always downgrade, because the database is
 empty and so an empty directory will be left. In particular, it won't
 contain `package.cache` file and then
 compiler/main/Packages.hs:readPackageConfig will fail on attempt to read
 this database, because it expects `package.cache`to be there.

 I see two possible solutions:

 1. We change the way we open database that contains a package for
 modification: instead of opening in read write mode and downgrading to
 read only if necessary, we first open in read only and only after we
 confirm that the database contains a package, we open in read write mode
 (and then unfortunately we also need to consider the possibility that the
 database changed between these two reads and downgrade to read only if the
 package is not there anymore). Although that still has a potential to
 create the problem if the database is removed between the first read only
 read and the subsequent read write read :/

 2. We modify compiler/main/Packages.hs:readPackageConfig to catch "not
 exists" error on reading `package.cache` file and check if the directory
 contains any `.conf` file. If so, we propagate the error (and possibly
 print slightly more user friendy message that cache is not there instead
 of `openBinaryFile: does not exist (No such file or directory)`), but if
 not, we consider the database to be empty.

 I think (2) is both simpler and more sensible. Thoughts?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13354#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list