From 6c0431877ca9faf8e5aab981a917922a9dcae12a Mon Sep 17 00:00:00 2001
From: Matthew Pickering <matthewtpickering@gmail.com>
Date: Thu, 17 Aug 2023 11:07:48 +0100
Subject: [PATCH] Generate build.mk for bindists

The config.mk.in script was relying on some variables which were
supposed to be set by build.mk but therefore never were when used to
install a bindist.

Specifically

* BUILD_PROF_LIBS to determine whether we had profiled libraries or not
* DYNAMIC_GHC_PROGRAMS to determine whether we had shared libraries or
  not

Not only were these never set but also not really accurate because you
could have shared libaries but still statically linked ghc executable.

In addition variables like GhcLibWays were just never used, so those
have been deleted from the script.

Now instead we generate a build.mk file which just directly specifies
which RtsWays we have supplied in the bindist and whether we have
DYNAMIC_GHC_PROGRAMS.
---
 hadrian/bindist/config.mk.in    | 56 +++------------------------------
 hadrian/src/Rules/BinaryDist.hs | 18 +++++++++++
 2 files changed, 22 insertions(+), 52 deletions(-)

diff --git a/hadrian/bindist/config.mk.in b/hadrian/bindist/config.mk.in
index c73a8aa3ffb6..ab4ae7a90579 100644
--- a/hadrian/bindist/config.mk.in
+++ b/hadrian/bindist/config.mk.in
@@ -27,6 +27,10 @@
 # string "${docdir}", not the value of docdir! This is crucial for the GNU
 # coding standards. See #1924.
 
+# The build.mk contains information about the bindist such as whether there are
+# profiled libraries.
+include build.mk
+
 define set_default
 # $1 = variable to set
 # $2 = default value to use, if configure didn't expand it
@@ -158,63 +162,11 @@ RelocatableBuild = NO
 endif
 
 
-# runhaskell and hsc2hs are special, in that other compilers besides
-# GHC might provide them.  Systems with a package manager often come
-# with tools to manage this kind of clash, e.g. RPM's
-# update-alternatives.  When building a distribution for such a system,
-# we recommend setting both of the following to 'YES'.
-#
-# NO_INSTALL_RUNHASKELL = YES
-# NO_INSTALL_HSC2HS     = YES
-#
-# NB. we use negative tests here because for binary-distributions we cannot
-# test build-time variables at install-time, so they must default to on.
 
 ifneq "$(DESTDIR)" ""
 override DESTDIR := $(abspath $(DESTDIR))
 endif
 
-# We build the libraries at least the "vanilla" way (way "v")
-# Technically we don't need the v way if DYNAMIC_GHC_PROGRAMS is YES,
-# but with -dynamic-too it's cheap, and makes life easier.
-GhcLibWays = v
-
-# In addition to the normal sequential way, the default is to also build
-# profiled prelude libraries
-# $(if $(filter ...)) allows controlling this expression from build.mk.
-GhcLibWays += $(if $(filter $(BUILD_PROF_LIBS),NO),,p)
-
-# Backward compatibility: although it would be cleaner to test for
-# PlatformSupportsSharedLibs, or perhaps a new variable BUILD_SHARED_LIBS,
-# some users currently expect that DYNAMIC_GHC_PROGRAMS=NO in build.mk implies
-# that dyn is not added to GhcLibWays.
-GhcLibWays += $(if $(filter $(DYNAMIC_GHC_PROGRAMS),NO),,dyn)
-
-# Handy way to test whether we're building shared libs or not.
-BuildSharedLibs=$(strip $(if $(findstring dyn,$(GhcLibWays)),YES,NO))
-
-# In addition, the RTS is built in some further variations.  Ways that
-# make sense here:
-#
-#   thr           : threaded
-#   thr_p         : threaded + profiled
-#   debug         : debugging
-#   thr_debug     : debugging + threaded
-#   p             : profiled
-#
-# While the eventlog used to be enabled in only a subset of ways, we now always
-# enable it.
-
-# Usually want the debug version
-GhcRTSWays = debug
-
-# We always have the threaded versions, but note that SMP support may be disabled
-# (see GhcWithSMP).
-GhcRTSWays += thr thr_debug
-GhcRTSWays += $(if $(findstring p, $(GhcLibWays)),thr_p,)
-GhcRTSWays += $(if $(findstring dyn, $(GhcLibWays)),dyn debug_dyn thr_dyn thr_debug_dyn,)
-GhcRTSWays += $(if $(findstring p, $(GhcLibWays)),thr_debug_p debug_p,)
-
 # We can only build GHCi threaded if we have a threaded RTS:
 GhcThreaded = $(if $(findstring thr,$(GhcRTSWays)),YES,NO)
 
diff --git a/hadrian/src/Rules/BinaryDist.hs b/hadrian/src/Rules/BinaryDist.hs
index 3ceb15393952..dfe2ec8d2beb 100644
--- a/hadrian/src/Rules/BinaryDist.hs
+++ b/hadrian/src/Rules/BinaryDist.hs
@@ -17,6 +17,8 @@ import qualified System.Directory.Extra as IO
 import Data.Either
 import GHC.Toolchain (ccProgram, tgtCCompiler, ccLinkProgram, tgtCCompilerLink)
 import GHC.Toolchain.Program (prgFlags)
+import qualified Data.Set as Set
+import Oracles.Flavour
 
 {-
 Note [Binary distributions]
@@ -262,6 +264,7 @@ bindistRules = do
           need $ map (bindistFilesDir -/-)
                     (["configure", "Makefile"] ++ bindistInstallFiles)
           copyFile ("hadrian" -/- "bindist" -/- "config.mk.in") (bindistFilesDir -/- "config.mk.in")
+          generateBuildMk >>= writeFile' (bindistFilesDir -/- "build.mk")
           copyFile ("hadrian" -/- "cfg" -/- "default.target.in") (bindistFilesDir -/- "default.target.in")
           copyFile ("hadrian" -/- "cfg" -/- "default.host.target.in") (bindistFilesDir -/- "default.host.target.in")
           forM_ bin_targets $ \(pkg, _) -> do
@@ -339,6 +342,21 @@ bindistRules = do
 data Compressor = Gzip | Bzip2 | Xz
                 deriving (Eq, Ord, Show)
 
+
+-- Information from the build configuration which needs to be propagated to config.mk.in
+generateBuildMk :: Action String
+generateBuildMk = do
+  dynamicGhc <- askDynGhcPrograms
+  rtsWays <- unwords . map show . Set.toList <$> interpretInContext (vanillaContext Stage1 rts) getRtsWays
+  return $ unlines [ "GhcRTSWays" =. rtsWays
+                   , "DYNAMIC_GHC_PROGRAMS" =. yesNo dynamicGhc ]
+
+
+  where
+    yesNo True = "YES"
+    yesNo False = "NO"
+    a =. b = a ++ " = " ++ b
+
 -- | Flag to pass to tar to use the given 'Compressor'.
 compressorTarFlag :: Compressor -> String
 compressorTarFlag Gzip  = "--gzip"
-- 
GitLab