[Git][ghc/ghc][wip/T22714] hadrian: Substitute LIBRARY_*_VERSION variables
Ben Gamari (@bgamari)
gitlab at gitlab.haskell.org
Sun Jan 29 16:11:54 UTC 2023
Ben Gamari pushed to branch wip/T22714 at Glasgow Haskell Compiler / GHC
Commits:
1bff1f03 by Ben Gamari at 2023-01-29T11:11:34-05:00
hadrian: Substitute LIBRARY_*_VERSION variables
This teaches Hadrian to substitute the `LIBRARY_*_VERSION` variables
in `libraries/prologue.txt`, fixing #22714.
Fixes #22714.
- - - - -
2 changed files:
- hadrian/src/Rules/Documentation.hs
- hadrian/src/Rules/Generate.hs
Changes:
=====================================
hadrian/src/Rules/Documentation.hs
=====================================
@@ -78,6 +78,8 @@ needDocDeps = do
, ghci
, libiserv
, compiler
+ , ghcHeap
+ , templateHaskell
]
need templatedCabalFiles
@@ -102,8 +104,6 @@ documentationRules = do
"docs" ~> do
root <- buildRoot
- needDocDeps
-
doctargets <- ghcDocs =<< flavour
let html = htmlRoot -/- "index.html" -- also implies "docs-haddock"
archives = map pathArchive docPaths
@@ -203,6 +203,9 @@ buildSphinxHtml path = do
root -/- htmlRoot -/- path -/- "index.html" %> \file -> do
let dest = takeDirectory file
rstFilesDir = pathPath path
+
+ needDocDeps
+
rstFiles <- getDirectoryFiles rstFilesDir ["**/*.rst"]
need (map (rstFilesDir -/-) rstFiles)
build $ target docContext (Sphinx HtmlMode) [pathPath path] [dest]
@@ -314,6 +317,9 @@ buildSphinxPdf :: FilePath -> Rules ()
buildSphinxPdf path = do
root <- buildRootRules
root -/- pdfRoot -/- path <.> "pdf" %> \file -> do
+
+ needDocDeps
+
withTempDir $ \dir -> do
let rstFilesDir = pathPath path
rstFiles <- getDirectoryFiles rstFilesDir ["**/*.rst"]
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -13,6 +13,8 @@ import Hadrian.Oracles.TextFile (lookupSystemConfig)
import Oracles.Flag
import Oracles.ModuleFiles
import Oracles.Setting
+import Hadrian.Haskell.Cabal.Type (PackageData(version))
+import Hadrian.Oracles.Cabal (readPackageData)
import Packages
import Rules.Libffi
import Settings
@@ -303,6 +305,13 @@ rtsCabalFlags = mconcat
where
flag = interpolateCabalFlag
+packageVersions :: Interpolations
+packageVersions = foldMap f [ base, ghcPrim, ghc, cabal, templateHaskell, ghcCompact, array ]
+ where
+ f :: Package -> Interpolations
+ f pkg = interpolateVar var $ show . version <$> readPackageData pkg
+ where var = "LIBRARY_" <> pkgName pkg <> "_VERSION"
+
templateRule :: FilePath -> Interpolations -> Rules ()
templateRule outPath interps = do
outPath %> \_ -> do
@@ -328,6 +337,7 @@ templateRules = do
templateRule "utils/ghc-pkg/ghc-pkg.cabal" $ projectVersion
templateRule "libraries/libiserv/libiserv.cabal" $ projectVersion
templateRule "libraries/template-haskell/template-haskell.cabal" $ projectVersion
+ templateRule "libraries/prologue.txt" $ packageVersions
-- Generators
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bff1f03ad790447b293652993459249a854a588
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bff1f03ad790447b293652993459249a854a588
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/20230129/e6234f7a/attachment-0001.html>
More information about the ghc-commits
mailing list