Skip to content
Snippets Groups Projects
Commit e23147f4 authored by Ben Gamari's avatar Ben Gamari
Browse files

users-guide: Refactor handling of :base-ref: et al.

(cherry picked from commit 8f82e99f)
parent 3359e6b4
No related branches found
No related tags found
No related merge requests found
......@@ -1159,20 +1159,6 @@ AC_SUBST(BUILD_MAN)
AC_SUBST(BUILD_SPHINX_HTML)
AC_SUBST(BUILD_SPHINX_PDF)
dnl ** Determine library versions
dnl The packages below should include all packages needed by
dnl doc/users_guide/ghc_config.py.in.
LIBRARY_VERSION(base)
LIBRARY_VERSION(Cabal, Cabal/Cabal/Cabal.cabal)
dnl template-haskell.cabal and ghc-prim.cabal are generated later
dnl by Hadrian but the .in files already have the version
LIBRARY_VERSION(template-haskell, template-haskell/template-haskell.cabal.in)
LIBRARY_VERSION(array)
LIBRARY_VERSION(ghc-prim, ghc-prim/ghc-prim.cabal.in)
LIBRARY_VERSION(ghc-compact)
LIBRARY_ghc_VERSION="$ProjectVersion"
AC_SUBST(LIBRARY_ghc_VERSION)
if grep ' ' compiler/ghc.cabal.in 2>&1 >/dev/null; then
AC_MSG_ERROR([compiler/ghc.cabal.in contains tab characters; please remove them])
fi
......
......@@ -18,14 +18,14 @@ libs_base_uri = '../libraries'
# N.B. If you add a package to this list be sure to also add a corresponding
# LIBRARY_VERSION macro call to configure.ac.
lib_versions = {
'base': '@LIBRARY_base_VERSION@',
'ghc-prim': '@LIBRARY_ghc_prim_VERSION@',
'template-haskell': '@LIBRARY_template_haskell_VERSION@',
'ghc-compact': '@LIBRARY_ghc_compact_VERSION@',
'ghc': '@LIBRARY_ghc_VERSION@',
'parallel': '@LIBRARY_parallel_VERSION@',
'Cabal': '@LIBRARY_Cabal_VERSION@',
'array': '@LIBRARY_array_VERSION@',
'base': '@LIBRARY_base_UNIT_ID@',
'ghc-prim': '@LIBRARY_ghc_prim_UNIT_ID@',
'template-haskell': '@LIBRARY_template_haskell_UNIT_ID@',
'ghc-compact': '@LIBRARY_ghc_compact_UNIT_ID@',
'ghc': '@LIBRARY_ghc_UNIT_ID@',
'parallel': '@LIBRARY_parallel_UNIT_ID@',
'Cabal': '@LIBRARY_Cabal_UNIT_ID@',
'array': '@LIBRARY_array_UNIT_ID@',
}
version = '@ProjectVersion@'
......
......@@ -313,6 +313,13 @@ packageVersions = foldMap f [ base, ghcPrim, compiler, ghc, cabal, templateHaske
f pkg = interpolateVar var $ version <$> readPackageData pkg
where var = "LIBRARY_" <> pkgName pkg <> "_VERSION"
packageUnitIds :: Interpolations
packageUnitIds = foldMap f [ base, ghcPrim, compiler, ghc, cabal, templateHaskell, ghcCompact, array ]
where
f :: Package -> Interpolations
f pkg = interpolateVar var $ pkgUnitId Stage1 pkg
where var = "LIBRARY_" <> pkgName pkg <> "_UNIT_ID"
templateRule :: FilePath -> Interpolations -> Rules ()
templateRule outPath interps = do
outPath %> \_ -> do
......@@ -339,6 +346,7 @@ templateRules = do
templateRule "libraries/template-haskell/template-haskell.cabal" $ projectVersion
templateRule "libraries/prologue.txt" $ packageVersions
templateRule "docs/index.html" $ packageVersions
templateRule "doc/users_guide/ghc_config.py" $ packageUnitIds
-- Generators
......
# LIBRARY_VERSION(lib, [cabal_file])
# --------------------------------
# Gets the version number of a library.
# If $1 is ghc-prim, then we define LIBRARY_ghc_prim_VERSION as 1.2.3
# $2 points to the directory under libraries/
AC_DEFUN([LIBRARY_VERSION],[
cabal_file=m4_default([$2],[$1/$1.cabal])
LIBRARY_[]translit([$1], [-], [_])[]_VERSION=`grep -i "^version:" libraries/${cabal_file} | sed "s/.* //"`
AC_SUBST(LIBRARY_[]translit([$1], [-], [_])[]_VERSION)
])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment