[Git][ghc/ghc][wip/hadrian-windows-bindist] 6 commits: hadrian: Uniformly pass buildOptions to all builders in runBuilder

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Fri Aug 18 08:57:22 UTC 2023



Matthew Pickering pushed to branch wip/hadrian-windows-bindist at Glasgow Haskell Compiler / GHC


Commits:
e2e26fb5 by Matthew Pickering at 2023-08-18T09:56:50+01:00
hadrian: Uniformly pass buildOptions to all builders in runBuilder

In Builder.hs, runBuilderWith mostly ignores the buildOptions in BuildInfo.

This leads to hard to diagnose bugs as any build options you pass with
runBuilderWithCmdOptions are ignored for many builders.

Solution: Uniformly pass buildOptions to the invocation of cmd.

Fixes #23845

- - - - -
ba5f2c21 by Matthew Pickering at 2023-08-18T09:56:50+01:00
Abstract windows toolchain setup

This commit splits up the windows toolchain setup logic into two
functions.

* FP_INSTALL_WINDOWS_TOOLCHAIN - deals with downloading the toolchain if
  it isn't already downloaded
* FP_SETUP_WINDOWS_TOOLCHAIN - sets the environment variables to point
  to the correct place

FP_SETUP_WINDOWS_TOOLCHAIN is abstracted from the location of the mingw
toolchain and also the eventual location where we will install the
toolchain in the installed bindist.

This is the first step towards #23608

- - - - -
8a4edfb7 by Matthew Pickering at 2023-08-18T09:56:50+01:00
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.

- - - - -
768b6b8c by Matthew Pickering at 2023-08-18T09:56:50+01:00
hadrian: Add reloc-binary-dist-* targets

This adds a command line option to build a "relocatable" bindist.

The bindist is created by first creating a normal bindist and then
installing it using the `RelocatableBuild=YES` option. This creates a
bindist without any wrapper scripts pointing to the libdir.

The motivation for this feature is that we want to ship relocatable
bindists on windows and this method is more uniform than the ad-hoc
method which lead to bugs such as #23608 and #23476

The relocatable bindist can be built with the "reloc-binary-dist" target
and supports the same suffixes as the normal "binary-dist" command to
specify the compression style.

- - - - -
34f2a743 by Matthew Pickering at 2023-08-18T09:56:50+01:00
packaging: Fix installation scripts on windows/RelocatableBuild case

This includes quite a lot of small fixes which fix the installation
makefile to work on windows properly. This also required fixing the
RelocatableBuild variable which seemed to have been broken for a long
while.

Sam helped me a lot writing this patch by providing a windows machine to
test the changes. Without him it would have taken ages to tweak
everything.

Co-authored-by: sheaf <sam.derbyshire at gmail.com>

- - - - -
24f82cd6 by Matthew Pickering at 2023-08-18T09:56:50+01:00
ci: Build relocatable bindist on windows

We now build the relocatable bindist target on windows, which means we
test and distribute the new method of creating a relocatable bindist.

- - - - -


11 changed files:

- .gitlab/ci.sh
- configure.ac
- distrib/configure.ac.in
- hadrian/README.md
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/src/Builder.hs
- hadrian/src/Hadrian/Builder/Ar.hs
- hadrian/src/Rules/BinaryDist.hs
- m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -490,8 +490,16 @@ function build_hadrian() {
   if [[ -n "${REINSTALL_GHC:-}" ]]; then
     run_hadrian build-cabal -V
   else
-    run_hadrian test:all_deps binary-dist -V
-    mv _build/bindist/ghc*.tar.xz "$BIN_DIST_NAME.tar.xz"
+    case "$(uname)" in
+        MSYS_*|MINGW*)
+          run_hadrian test:all_deps reloc-binary-dist -V
+          mv _build/reloc-bindist/ghc*.tar.xz "$BIN_DIST_NAME.tar.xz"
+          ;;
+        *)
+          run_hadrian test:all_deps binary-dist -V
+          mv _build/bindist/ghc*.tar.xz "$BIN_DIST_NAME.tar.xz"
+          ;;
+    esac
   fi
 
 }


=====================================
configure.ac
=====================================
@@ -346,7 +346,8 @@ FP_FIND_ROOT
 
 # Extract and configure the Windows toolchain
 if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO"; then
-    FP_SETUP_WINDOWS_TOOLCHAIN
+    FP_INSTALL_WINDOWS_TOOLCHAIN
+    FP_SETUP_WINDOWS_TOOLCHAIN([$hardtop/inplace/mingw], [$hardtop/inplace/mingw])
 else
     AC_PATH_TOOL([CC],[gcc], [clang])
     AC_PATH_TOOL([CXX],[g++], [clang++])


=====================================
distrib/configure.ac.in
=====================================
@@ -103,6 +103,17 @@ AC_ARG_ENABLE(distro-toolchain,
   [EnableDistroToolchain=@SettingsUseDistroMINGW@]
 )
 
+if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO"; then
+  FP_SETUP_WINDOWS_TOOLCHAIN([$hardtop/mingw/], [\$\$topdir/../mingw/])
+fi
+
+if test "$HostOS" = "mingw32"; then
+    WindresCmd="$Windres"
+    AC_SUBST([WindresCmd])
+    AC_SUBST([GenlibCmd])
+    AC_SUBST([HAVE_GENLIB])
+fi
+
 dnl ** Which gcc to use?
 dnl --------------------------------------------------------------
 AC_PROG_CC([gcc clang])
@@ -288,6 +299,7 @@ if test "x$UseLibdw" = "xYES" ; then
 fi
 AC_SUBST(UseLibdw)
 
+
 FP_SETTINGS
 
 AC_CONFIG_FILES([config.mk])


=====================================
hadrian/README.md
=====================================
@@ -325,6 +325,13 @@ $ ./configure [--prefix=PATH] && make install
 
 workflow, for now.
 
+Note: On windows you need to use the `reloc-binary-dist` target.
+
+#### Relocatable Binary Distribution
+
+If you require a relocatable binary distribution (for example on Windows), then you
+can build the `reloc-binary-dist` target.
+
 ### Building and installing GHC
 
 You can get Hadrian to build _and_ install a binary distribution in one go


=====================================
hadrian/bindist/Makefile
=====================================
@@ -63,19 +63,28 @@ show:
 .PHONY: install
 
 ifeq "$(TargetOS_CPP)" "mingw32"
-install_bin: install_mingw install_bin_direct
+install_extra: install_mingw
+else
+install_extra:
+endif
+
+ifeq "$(RelocatableBuild)" "YES"
+install_bin: install_bin_direct
 else
 install_bin: install_bin_libdir install_wrappers
 endif
 
-install: install_bin install_lib
+
+
+install: install_bin install_lib install_extra
 install: install_man install_docs update_package_db
 
-ActualBinsDir=${ghclibdir}/bin
 ifeq "$(RelocatableBuild)" "YES"
 ActualLibsDir=${ghclibdir}
+ActualBinsDir=${bindir}
 else
 ActualLibsDir=${ghclibdir}/lib
+ActualBinsDir=${ghclibdir}/bin
 endif
 WrapperBinsDir=${bindir}
 


=====================================
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
@@ -63,6 +67,12 @@ $(eval $(call set_default,dvidir,$${docdir}))
 $(eval $(call set_default,pdfdir,$${docdir}))
 $(eval $(call set_default,psdir,$${docdir}))
 
+# On Windows we normally want to make a relocatable bindist, to we
+# ignore flags like libdir
+ifeq "$(Windows_Host)" "YES"
+RelocatableBuild = YES
+endif
+
 ifeq "$(RelocatableBuild)" "YES"
 
 # Hack: our directory layouts tend to be different on Windows, so
@@ -149,72 +159,12 @@ else
 GhcWithInterpreter=$(if $(findstring YES,$(DYNAMIC_GHC_PROGRAMS)),YES,NO)
 endif
 
-# On Windows we normally want to make a relocatable bindist, to we
-# ignore flags like libdir
-ifeq "$(Windows_Host)" "YES"
-RelocatableBuild = YES
-else
-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)
 


=====================================
hadrian/src/Builder.hs
=====================================
@@ -313,20 +313,20 @@ instance H.Builder Builder where
                 msgOut = "[runBuilderWith] Exactly one output file expected."
                 -- Capture stdout and write it to the output file.
                 captureStdout = do
-                    Stdout stdout <- cmd' [path] buildArgs
+                    Stdout stdout <- cmd' [path] buildArgs buildOptions
                     -- see Note [Capture stdout as a ByteString]
                     writeFileChangedBS output stdout
             case builder of
                 Ar Pack stg -> do
                     useTempFile <- arSupportsAtFile stg
-                    if useTempFile then runAr                path buildArgs buildInputs
-                                   else runArWithoutTempFile path buildArgs buildInputs
+                    if useTempFile then runAr                path buildArgs buildInputs buildOptions
+                                   else runArWithoutTempFile path buildArgs buildInputs buildOptions
 
-                Ar Unpack _ -> cmd' [Cwd output] [path] buildArgs
+                Ar Unpack _ -> cmd' [Cwd output] [path] buildArgs buildOptions
 
                 Autoreconf dir -> do
                   bash <- bashPath
-                  cmd' [Cwd dir] [bash, path] buildArgs
+                  cmd' [Cwd dir] [bash, path] buildArgs buildOptions
 
                 Configure  dir -> do
                     -- Inject /bin/bash into `libtool`, instead of /bin/sh,
@@ -339,7 +339,7 @@ instance H.Builder Builder where
 
                 GenPrimopCode -> do
                     stdin <- readFile' input
-                    Stdout stdout <- cmd' (Stdin stdin) [path] buildArgs
+                    Stdout stdout <- cmd' (Stdin stdin) [path] buildArgs buildOptions
                     -- see Note [Capture stdout as a ByteString]
                     writeFileChangedBS output stdout
 
@@ -350,47 +350,47 @@ instance H.Builder Builder where
                       , "describe"
                       , input -- the package name
                       ]
-                    cmd' (Stdin pkgDesc) [path] (buildArgs ++ ["-"])
+                    cmd' (Stdin pkgDesc) [path] (buildArgs ++ ["-"]) buildOptions
 
                 GhcPkg Unregister _ -> do
                     -- unregistering is allowed to fail (e.g. when a package
                     -- isn't already present)
-                    Exit _ <- cmd' [path] (buildArgs ++ [input])
+                    Exit _ <- cmd' [path] (buildArgs ++ [input]) buildOptions
                     return ()
 
                 Haddock BuildPackage -> runHaddock path buildArgs buildInputs
 
                 HsCpp    -> captureStdout
 
-                Make dir -> cmd' path ["-C", dir] buildArgs
+                Make dir -> cmd' buildOptions path ["-C", dir] buildArgs
 
                 Makeinfo -> do
-                  cmd' [path] "--no-split" [ "-o", output] [input]
+                  cmd' [path] "--no-split" [ "-o", output] [input] buildOptions
 
                 Xelatex   ->
                   -- xelatex produces an incredible amount of output, almost
                   -- all of which is useless. Suppress it unless user
                   -- requests a loud build.
                   if verbosity >= Diagnostic
-                    then cmd' [Cwd output] [path] buildArgs
-                    else do (Stdouterr out, Exit code) <- cmd' [Cwd output] [path] buildArgs
+                    then cmd' [Cwd output] [path] buildArgs buildOptions
+                    else do (Stdouterr out, Exit code) <- cmd' [Cwd output] [path] buildArgs buildOptions
                             when (code /= ExitSuccess) $ do
                               liftIO $ BSL.hPutStrLn stderr out
                               putFailure "xelatex failed!"
                               fail "xelatex failed"
 
-                Makeindex -> unit $ cmd' [Cwd output] [path] (buildArgs ++ [input])
+                Makeindex -> unit $ cmd' [Cwd output] [path] (buildArgs ++ [input]) buildOptions
 
                 Tar _ -> cmd' buildOptions [path] buildArgs
 
                 -- RunTest produces a very large amount of (colorised) output;
                 -- Don't attempt to capture it.
                 Testsuite RunTest -> do
-                  Exit code <- cmd [path] buildArgs
+                  Exit code <- cmd [path] buildArgs buildOptions
                   when (code /= ExitSuccess) $ do
                     fail "tests failed"
 
-                _  -> cmd' [path] buildArgs
+                _  -> cmd' [path] buildArgs buildOptions
 
 -- | Invoke @haddock@ given a path to it and a list of arguments. The arguments
 -- are passed in a response file.


=====================================
hadrian/src/Hadrian/Builder/Ar.hs
=====================================
@@ -38,10 +38,11 @@ instance NFData   ArMode
 runAr :: FilePath    -- ^ path to @ar@
       -> [String]    -- ^ other arguments
       -> [FilePath]  -- ^ input file paths
+      -> [CmdOption] -- ^ Additional options
       -> Action ()
-runAr arPath flagArgs fileArgs = withTempFile $ \tmp -> do
+runAr arPath flagArgs fileArgs buildOptions = withTempFile $ \tmp -> do
     writeFile' tmp $ unwords fileArgs
-    cmd [arPath] flagArgs ('@' : tmp)
+    cmd [arPath] flagArgs ('@' : tmp) buildOptions
 
 -- | Invoke @ar@ given a path to it and a list of arguments. Note that @ar@
 -- will be called multiple times if the list of files to be archived is too
@@ -50,7 +51,8 @@ runAr arPath flagArgs fileArgs = withTempFile $ \tmp -> do
 runArWithoutTempFile :: FilePath    -- ^ path to @ar@
                      -> [String]    -- ^ other arguments
                      -> [FilePath]  -- ^ input file paths
+                     -> [CmdOption] -- ^ Additional options
                      -> Action ()
-runArWithoutTempFile arPath flagArgs fileArgs =
+runArWithoutTempFile arPath flagArgs fileArgs buildOptions =
     forM_ (chunksOfSize cmdLineLengthLimit fileArgs) $ \argsChunk ->
-        unit . cmd [arPath] $ flagArgs ++ argsChunk
+        unit (cmd [arPath] (flagArgs ++ argsChunk) buildOptions)


=====================================
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]
@@ -108,20 +110,40 @@ other, the install script:
 
 -}
 
+data Relocatable = Relocatable | NotRelocatable
+
+installTo :: Relocatable -> String -> Action ()
+installTo relocatable prefix = do
+    root <- buildRoot
+    version        <- setting ProjectVersion
+    targetPlatform <- setting TargetPlatformFull
+    let ghcVersionPretty = "ghc-" ++ version ++ "-" ++ targetPlatform
+        bindistFilesDir  = root -/- "bindist" -/- ghcVersionPretty
+    runBuilder (Configure bindistFilesDir) ["--prefix="++prefix] [] []
+    let env = case relocatable of
+                Relocatable -> [AddEnv "RelocatableBuild" "YES"]
+                NotRelocatable -> []
+    runBuilderWithCmdOptions env (Make bindistFilesDir) ["install"] [] []
+
 bindistRules :: Rules ()
 bindistRules = do
     root <- buildRootRules
-    phony "install" $ do
+    phony "reloc-binary-dist-dir" $ do
         need ["binary-dist-dir"]
+        cwd <- liftIO $ IO.getCurrentDirectory
         version        <- setting ProjectVersion
         targetPlatform <- setting TargetPlatformFull
         let ghcVersionPretty = "ghc-" ++ version ++ "-" ++ targetPlatform
-            bindistFilesDir  = root -/- "bindist" -/- ghcVersionPretty
-            prefixErr = "You must specify a path with --prefix when using the"
+        let prefix = cwd -/- root -/- "reloc-bindist" -/- ghcVersionPretty
+        installTo Relocatable prefix
+
+
+    phony "install" $ do
+        need ["binary-dist-dir"]
+        let prefixErr = "You must specify a path with --prefix when using the"
                      ++ " 'install' rule"
         installPrefix <- fromMaybe (error prefixErr) <$> cmdPrefix
-        runBuilder (Configure bindistFilesDir) ["--prefix="++installPrefix] [] []
-        runBuilder (Make bindistFilesDir) ["install"] [] []
+        installTo NotRelocatable installPrefix
 
     phony "binary-dist-dir" $ do
         -- We 'need' all binaries and libraries
@@ -207,16 +229,6 @@ bindistRules = do
         cmd_ (bindistFilesDir -/- "bin" -/- ghcPkgName) ["recache"]
 
 
-        -- The settings file must be regenerated by the bindist installation
-        -- logic to account for the environment discovered by the bindist
-        -- configure script on the host. Not on Windows, however, where
-        -- we do not ship a configure script with the bindist. See #20254.
-        --
-        -- N.B. we must do this after ghc-pkg has been run as it will go
-        -- looking for the settings files.
-        unless windowsHost $
-            removeFile (bindistFilesDir -/- "lib" -/- "settings")
-
         unless cross $ need ["docs"]
 
         -- TODO: we should only embed the docs that have been generated
@@ -250,41 +262,40 @@ bindistRules = do
         whenM (liftIO (IO.doesDirectoryExist (root -/- "manpage"))) $ do
           copyDirectory (root -/- "manpage") bindistFilesDir
 
-        -- These scripts are only necessary in the configure/install
-        -- workflow which is not supported on windows.
-        -- TODO: Instead of guarding against windows, we could offer the
-        -- option to make a relocatable, but not installable bindist on any
-        -- platform.
-        unless windowsHost $ do
-          -- We then 'need' all the files necessary to configure and install
-          -- (as in, './configure [...] && make install') this build on some
-          -- other machine.
-          need $ map (bindistFilesDir -/-)
-                    (["configure", "Makefile"] ++ bindistInstallFiles)
-          copyFile ("hadrian" -/- "bindist" -/- "config.mk.in") (bindistFilesDir -/- "config.mk.in")
-          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
-            needed_wrappers <- pkgToWrappers pkg
-            forM_ needed_wrappers $ \wrapper_name -> do
-              let suffix = if useGhcPrefix pkg
-                             then "ghc-" ++ version
-                             else version
-              wrapper_content <- wrapper wrapper_name
-              let unversioned_wrapper_path = bindistFilesDir -/- "wrappers" -/- wrapper_name
-                  versioned_wrapper = wrapper_name ++ "-" ++ suffix
-                  versioned_wrapper_path = bindistFilesDir -/- "wrappers" -/- versioned_wrapper
-              -- Write the wrapper to the versioned path
-              writeFile' versioned_wrapper_path wrapper_content
-              -- Create a symlink from the non-versioned to the versioned.
-              liftIO $ do
-                IO.removeFile unversioned_wrapper_path <|> return ()
-                IO.createFileLink versioned_wrapper unversioned_wrapper_path
-
-
-    let buildBinDist :: Compressor -> Action ()
-        buildBinDist compressor = do
-            need ["binary-dist-dir"]
+        -- We then 'need' all the files necessary to configure and install
+        -- (as in, './configure [...] && make install') this build on some
+        -- other machine.
+        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")
+
+        -- todo: do we need these wrappers on windows
+        forM_ bin_targets $ \(pkg, _) -> do
+          needed_wrappers <- pkgToWrappers pkg
+          forM_ needed_wrappers $ \wrapper_name -> do
+            let suffix = if useGhcPrefix pkg
+                           then "ghc-" ++ version
+                           else version
+            wrapper_content <- wrapper wrapper_name
+            let unversioned_wrapper_path = bindistFilesDir -/- "wrappers" -/- wrapper_name
+                versioned_wrapper = wrapper_name ++ "-" ++ suffix
+                versioned_wrapper_path = bindistFilesDir -/- "wrappers" -/- versioned_wrapper
+            -- Write the wrapper to the versioned path
+            writeFile' versioned_wrapper_path wrapper_content
+            -- Create a symlink from the non-versioned to the versioned.
+            liftIO $ do
+              IO.removeFile unversioned_wrapper_path <|> return ()
+              IO.createFileLink versioned_wrapper unversioned_wrapper_path
+
+    let buildBinDist = buildBinDistX "binary-dist-dir" "bindist"
+        buildBinDistReloc = buildBinDistX "reloc-binary-dist-dir" "reloc-bindist"
+
+        buildBinDistX :: String -> FilePath -> Compressor -> Action ()
+        buildBinDistX target bindist_folder compressor = do
+            need [target]
 
             version        <- setting ProjectVersion
             targetPlatform <- setting TargetPlatformFull
@@ -293,15 +304,16 @@ bindistRules = do
 
             -- Finally, we create the archive <root>/bindist/ghc-X.Y.Z-platform.tar.xz
             tarPath <- builderPath (Tar Create)
-            cmd [Cwd $ root -/- "bindist"] tarPath
+            cmd [Cwd $ root -/- bindist_folder] tarPath
                 [ "-c", compressorTarFlag compressor, "-f"
                 , ghcVersionPretty <.> "tar" <.> compressorExtension compressor
                 , ghcVersionPretty ]
 
-    phony "binary-dist" $ buildBinDist Xz
-    phony "binary-dist-gzip" $ buildBinDist Gzip
-    phony "binary-dist-bzip2" $ buildBinDist Bzip2
-    phony "binary-dist-xz" $ buildBinDist Xz
+    forM_ [("binary", buildBinDist), ("reloc-binary", buildBinDistReloc)] $ \(name, mk_bindist) -> do
+      phony (name <> "-dist") $ mk_bindist Xz
+      phony (name <> "-dist-gzip") $ mk_bindist Gzip
+      phony (name <> "-dist-bzip2") $ mk_bindist Bzip2
+      phony (name <> "-dist-xz") $ mk_bindist Xz
 
     -- Prepare binary distribution configure script
     -- (generated under <ghc root>/distrib/configure by 'autoreconf')
@@ -339,6 +351,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"


=====================================
m4/fp_settings.m4
=====================================
@@ -43,7 +43,7 @@ dnl ghc-toolchain.
 AC_DEFUN([SUBST_TOOLDIR],
 [
     dnl and Note [How we configure the bundled windows toolchain]
-    $1=`echo $$1 | sed 's%'"$mingwpath"'%$$tooldir/mingw%'`
+    $1=`echo "$$1" | sed 's%'"$mingw_prefix"'%'"$mingw_install_prefix"'%g'`
 ])
 
 # FP_SETTINGS


=====================================
m4/fp_setup_windows_toolchain.m4
=====================================
@@ -1,4 +1,5 @@
-AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
+# Download and install the windows toolchain
+AC_DEFUN([FP_INSTALL_WINDOWS_TOOLCHAIN],[
     # Find the mingw-w64 archive file to extract.
     if test "$HostArch" = "i386"
     then
@@ -72,18 +73,29 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
     # NB. Download and extract the MingW-w64 distribution if required
     set_up_tarballs
 
+])
+
+# Set up the environment variables
+# The actual location of the windows toolchain (before install)
+# $2 the location that the windows toolchain will be installed in relative to the libdir
+AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
+
     # N.B. The parameters which get plopped in the `settings` file used by the
     # resulting compiler are computed in `FP_SETTINGS`. Specifically, we use
     # $$topdir-relative paths instead of fullpaths to the toolchain, by replacing
     # occurrences of $hardtop/inplace/mingw with $$tooldir/mingw
 
+    mingw_prefix="$1"
+    mingw_install_prefix="$2"
+#    mingwpath="$hardtop/inplace/mingw"
+
     # Our Windows toolchain is based around Clang and LLD. We use compiler-rt
     # for the runtime, libc++ and libc++abi for the C++ standard library
     # implementation, and libunwind for C++ unwinding.
-    mingwbin="$hardtop/inplace/mingw/bin/"
-    mingwlib="$hardtop/inplace/mingw/lib"
-    mingwinclude="$hardtop/inplace/mingw/include"
-    mingwpath="$hardtop/inplace/mingw"
+    mingwbin="$mingw_prefix/bin/"
+    mingwlib="$mingw_prefix/lib"
+    mingwinclude="$mingw_prefix/include"
+    mingw_mingw32_lib="$mingw_prefix/x86_64-w64-mingw32/lib"
 
     CC="${mingwbin}clang.exe"
     CXX="${mingwbin}clang++.exe"
@@ -106,8 +118,8 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
 
     HaskellCPPArgs="$HaskellCPPArgs -I$mingwinclude"
 
-    CONF_GCC_LINKER_OPTS_STAGE1="-fuse-ld=lld $cflags -L$mingwlib -L$hardtop/inplace/mingw/x86_64-w64-mingw32/lib"
-    CONF_GCC_LINKER_OPTS_STAGE2="-fuse-ld=lld $cflags -L$mingwlib -L$hardtop/inplace/mingw/x86_64-w64-mingw32/lib"
+    CONF_GCC_LINKER_OPTS_STAGE1="-fuse-ld=lld $cflags -L$mingwlib -L$mingw_mingw32_lib"
+    CONF_GCC_LINKER_OPTS_STAGE2="-fuse-ld=lld $cflags -L$mingwlib -L$mingw_mingw32_lib"
 
     # N.BOn Windows we can't easily dynamically-link against libc++ since there is
     # no RPATH support, meaning that the loader will have no way of finding our



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40074cf9bb35629d190956e2705c186640840831...24f82cd602b803b3183b6c85313bd1c33cd9031d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40074cf9bb35629d190956e2705c186640840831...24f82cd602b803b3183b6c85313bd1c33cd9031d
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/20230818/c059b586/attachment-0001.html>


More information about the ghc-commits mailing list