Skip to content
Snippets Groups Projects
Verified Commit bf34a310 authored by Ben Gamari's avatar Ben Gamari Committed by Moritz Angermann
Browse files

hadrian: Don't depend upon bash from PATH

Previously Hadrian depended implicitly upon whatever `bash` it found in
`PATH`, offerring no way for the user to override. Fix this by detecting
`sh` in `configure` and passing the result to Hadrian.

Fixes #19797.
parent 049c3a83
No related branches found
No related tags found
No related merge requests found
......@@ -255,6 +255,8 @@ AC_CANONICAL_TARGET
FPTOOLS_SET_PLATFORM_VARS
FP_PROG_SH
# Verify that the installed (bootstrap) GHC is capable of generating
# code for the requested build platform.
if test "$BuildPlatform" != "$bootstrap_target"
......
......@@ -28,6 +28,7 @@ patch = @PatchCmd@
xelatex = @XELATEX@
makeindex = @MAKEINDEX@
makeinfo = @MAKEINFO@
bourne-shell = @SH@
# Python 3 is required to run test driver.
# See: https://github.com/ghc/ghc/blob/master/testsuite/mk/boilerplate.mk#L220
......
......@@ -27,6 +27,7 @@ import Hadrian.Builder.Tar
import Hadrian.Oracles.Path
import Hadrian.Oracles.TextFile
import Hadrian.Utilities
import Oracles.Setting (bashPath)
import System.Exit
import System.IO (stderr)
......@@ -254,7 +255,9 @@ instance H.Builder Builder where
Ar Unpack _ -> cmd' echo [Cwd output] [path] buildArgs
Autoreconf dir -> cmd' echo [Cwd dir] ["sh", path] buildArgs
Autoreconf dir -> do
bash <- bashPath
cmd' echo [Cwd dir] [bash, path] buildArgs
Configure dir -> do
-- Inject /bin/bash into `libtool`, instead of /bin/sh,
......
{-# LANGUAGE TypeFamilies #-}
module Hadrian.Oracles.Path (
lookupInPath, bashPath, fixAbsolutePathOnWindows, pathOracle
lookupInPath, fixAbsolutePathOnWindows, pathOracle
) where
import Control.Monad
......@@ -20,10 +20,6 @@ lookupInPath name
| name == takeFileName name = askOracle $ LookupInPath name
| otherwise = return name
-- | Lookup the path to the @bash@ interpreter.
bashPath :: Action FilePath
bashPath = lookupInPath "bash"
-- | Fix an absolute path on Windows:
-- * "/c/" => "C:/"
-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe"
......
......@@ -7,7 +7,7 @@ module Oracles.Setting (
-- * Helpers
ghcCanonVersion, cmdLineLengthLimit, hostSupportsRPaths, topDirectory,
libsuf, ghcVersionStage,
libsuf, ghcVersionStage, bashPath,
-- ** Target platform things
anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs,
......@@ -76,6 +76,7 @@ data Setting = BuildArch
| TargetArchHaskell
| TargetOsHaskell
| TargetArmVersion
| BourneShell
-- TODO: Reduce the variety of similar flags (e.g. CPP and non-CPP versions).
-- | Each 'SettingList' comes from the file @hadrian/cfg/system.config@,
......@@ -172,6 +173,7 @@ setting key = lookupValueOrError configFile $ case key of
TargetVendor -> "target-vendor"
TargetArchHaskell -> "target-arch-haskell"
TargetOsHaskell -> "target-os-haskell"
BourneShell -> "bourne-shell"
-- | Look up the value of a 'SettingList' in @cfg/system.config@, tracking the
-- result.
......@@ -217,6 +219,10 @@ settingsFileSetting key = lookupValueOrError configFile $ case key of
getSetting :: Setting -> Expr c b String
getSetting = expr . setting
-- | The path to a Bourne shell interpreter.
bashPath :: Action FilePath
bashPath = setting BourneShell
-- | An expression that looks up the value of a 'SettingList' in
-- @cfg/system.config@, tracking the result.
getSettingList :: SettingList -> Args c b
......
# FP_PROG_SH
# ------------
# Find a functional Bourne shell
AC_DEFUN([FP_PROG_SH],
[
AC_REQUIRE([FPTOOLS_SET_PLATFORM_VARS]) dnl for $windows
AC_ARG_VAR(SH,[Use as the full path to a Bourne shell. [default=autodetect]])
AC_PATH_PROGS([SH], [sh bash])
if test "$windows" = "YES"; then
dnl use mixed (-m) mode to get C:/mingw64/... with forward slashes.
dnl windows (-w) mode will give us C:\... and mess with escaping.
SH=`cygpath -m "$SH"`
fi
AC_SUBST([SH])[]dnl
])# FP_PROG_SH
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