[Git][ghc/ghc][wip/hadrian-windows-bindist] generate build.mk
Matthew Pickering (@mpickering)
gitlab at gitlab.haskell.org
Wed Aug 16 15:29:48 UTC 2023
Matthew Pickering pushed to branch wip/hadrian-windows-bindist at Glasgow Haskell Compiler / GHC
Commits:
13995dd9 by Matthew Pickering at 2023-08-16T16:29:25+01:00
generate build.mk
- - - - -
2 changed files:
- hadrian/bindist/config.mk.in
- hadrian/src/Rules/BinaryDist.hs
Changes:
=====================================
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
@@ -67,7 +71,6 @@ $(eval $(call set_default,psdir,$${docdir}))
# ignore flags like libdir
ifeq "$(Windows_Host)" "YES"
RelocatableBuild = YES
-DYNAMIC_GHC_PROGRAMS = NO
endif
ifeq "$(RelocatableBuild)" "YES"
@@ -158,63 +161,10 @@ 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)
=====================================
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]
@@ -261,6 +263,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")
@@ -344,6 +347,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"
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13995dd998fa5a6f2fbfc1cdc9231bbf6e986a5d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13995dd998fa5a6f2fbfc1cdc9231bbf6e986a5d
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/20230816/aad21b11/attachment-0001.html>
More information about the ghc-commits
mailing list