[Git][ghc/ghc][master] Hadrian: need CPP preprocessor dependencies #16660

Marge Bot gitlab at gitlab.haskell.org
Sun Jun 9 22:46:52 UTC 2019



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


Commits:
69c58f8a by David Eichmann at 2019-06-09T22:46:46Z
Hadrian: need CPP preprocessor dependencies #16660

Use the new -include-cpp-deps ghc option (#16521)
when generating .dependencies files in hadrian.
This is version gated as -include-cpp-deps is a
relatively new option.

- - - - -


1 changed file:

- hadrian/src/Settings/Builders/Ghc.hs


Changes:

=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -1,5 +1,9 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+
 module Settings.Builders.Ghc (ghcBuilderArgs, haddockGhcArgs) where
 
+import Data.List.Extra (splitOn)
+
 import Hadrian.Haskell.Cabal
 import Hadrian.Haskell.Cabal.Type
 
@@ -131,7 +135,16 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
 findHsDependencies :: Args
 findHsDependencies = builder (Ghc FindHsDependencies) ? do
     ways <- getLibraryWays
+    stage <- getStage
+    ghcVersion :: [Int] <- fmap read . splitOn "." <$> expr (ghcVersionStage stage)
     mconcat [ arg "-M"
+
+            -- "-include-cpp-deps" is a new ish feature so is version gated.
+            -- Without this feature some dependencies will be missing in stage0.
+            -- TODO Remove version gate when minimum supported Stage0 compiler
+            -- is >= 8.9.0.
+            , ghcVersion > [8,9,0] ? arg "-include-cpp-deps"
+
             , commonGhcArgs
             , arg "-include-pkg-deps"
             , arg "-dep-makefile", arg =<< getOutput



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/69c58f8abbb0b51eca1f0004a8d8c1cee0c8f766

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/69c58f8abbb0b51eca1f0004a8d8c1cee0c8f766
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/20190609/1621897e/attachment-0001.html>


More information about the ghc-commits mailing list