[Git][ghc/ghc][master] 2 commits: hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468.

Marge Bot gitlab at gitlab.haskell.org
Wed Aug 5 07:58:56 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00
hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468.

In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db`
was already given correctly to tell `stage0/bin/ghc-pkg` that it should use
the package DB in `stage1/`.

However, `ghc` needs to be given this information as well, not only `ghc-pkg`!
Until now that was not the case; the package DB in `stage0` was given to
`ghc` instead.
This was wrong, because there is no binary compatibility guarantee that says
that the `stage0` DB's `package.cache` (which is written by the
stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg`
from the source code tree.

As a result, when trying to add fields to `InstalledPackageInfo` that get
serialised into / deserialised from the `package.cache`, errors like

    _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!)

would appear. This was because the `stage0/bin/ghc would try to
deserialise the newly added fields from
`_build/stage0/lib/package.conf.d/package.cache`, but they were not in there
because the system `ghc-pkg` doesn't know about them and thus didn't write them
there.
It would try to do that because any GHC by default tries to read the global
package db in `../lib/package.conf.d/package.cache`.
For `stage0/bin/ghc` that *can never work* as explained above, so we
must disable this default via `-no-global-package-db` and give it the
correct package DB explicitly.

This is the same problem as #16534, and the same fix as in MR !780
(but in another context; that one was for developers trying out the
`stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix
is for a `cabal configure` invocation).

I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`,
and have fixed that in this commit as well.
It only worked until now because nobody tried to add a new ghc-pkg `.conf`
field since the introduction of Hadrian.

- - - - -
ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00
Hardcode RTS includes to cope with unregistered builds

- - - - -


3 changed files:

- compiler/GHC/Driver/CodeOutput.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Cabal.hs


Changes:

=====================================
compiler/GHC/Driver/CodeOutput.hs
=====================================
@@ -125,27 +125,10 @@ outputC :: DynFlags
 outputC dflags filenm cmm_stream packages
   = do
        withTiming dflags (text "C codegen") (\a -> seq a () {- FIXME -}) $ do
-
-         -- figure out which header files to #include in the generated .hc file:
-         --
-         --   * extra_includes from packages
-         --   * -#include options from the cmdline and OPTIONS pragmas
-         --   * the _stub.h file, if there is one.
-         --
-         let rts = unsafeLookupUnitId (unitState dflags) rtsUnitId
-
-         let cc_injects = unlines (map mk_include (unitIncludes rts))
-             mk_include h_file =
-              case h_file of
-                 '"':_{-"-} -> "#include "++h_file
-                 '<':_      -> "#include "++h_file
-                 _          -> "#include \""++h_file++"\""
-
          let pkg_names = map unitIdString packages
-
          doOutput filenm $ \ h -> do
             hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
-            hPutStr h cc_injects
+            hPutStr h "#include \"Stg.h\"\n"
             let platform = targetPlatform dflags
                 writeC = printForC dflags h . cmmToC platform
             Stream.consume cmm_stream writeC


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -218,7 +218,11 @@ ghcWrapper stage  = do
     ghcPath <- expr $ (</>) <$> topDirectory
                             <*> programPath (vanillaContext (pred stage) ghc)
     return $ unwords $ map show $ [ ghcPath ]
-                               ++ [ "-package-db " ++ dbPath | stage == Stage1 ]
+                               ++ (if stage == Stage1
+                                     then ["-no-global-package-db"
+                                          , "-package-db " ++ dbPath
+                                          ]
+                                     else [])
                                ++ [ "$@" ]
 
 -- | Given a 'String' replace characters '.' and '-' by underscores ('_') so that


=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -49,6 +49,7 @@ cabalBuilderArgs = builder (Cabal Setup) ? do
             , arg $ "${pkgroot}/../../docs/html/libraries/" ++ pkgName pkg
 
             , withStaged $ Ghc CompileHs
+            , withBuilderArgs (Ghc CompileHs stage)
             , withStaged (GhcPkg Update)
             , withBuilderArgs (GhcPkg Update stage)
             , bootPackageDatabaseArgs
@@ -159,6 +160,14 @@ withBuilderKey b = case b of
 -- | Add arguments to builders if needed.
 withBuilderArgs :: Builder -> Args
 withBuilderArgs b = case b of
+    Ghc _ stage -> do
+      top   <- expr topDirectory
+      pkgDb <- expr $ packageDbPath stage
+      -- GHC starts with a nonempty package DB stack, so we need to tell it
+      -- to empty the stack first for it to truly consider only the package
+      -- DB we explicitly provide. See #17468.
+      notStage0 ? arg ("--ghc-option=-no-global-package-db") <>
+                  arg ("--ghc-option=-package-db=" ++ top -/- pkgDb)
     GhcPkg _ stage -> do
       top   <- expr topDirectory
       pkgDb <- expr $ packageDbPath stage



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2d1accf67cb6e1dab6b2c78fef4b64526c31a4a...ef2ae81a394df573510b12b7e11bba0c931249d8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2d1accf67cb6e1dab6b2c78fef4b64526c31a4a...ef2ae81a394df573510b12b7e11bba0c931249d8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200805/cc017975/attachment-0001.html>


More information about the ghc-commits mailing list