Skip to content

Commit

Permalink
Introduce a $tooldir variable for nicer toolchain detection on Windows
Browse files Browse the repository at this point in the history
This patch affects several files that affect how we detect mingw and perl
on Windows. The initial motivation is:

    snowleopard/hadrian#564

where, with Hadrian building relocatable (non-inplace) GHCs, the current
detection mechanism falls short by e.g only trying $topdir/../mingw. But
in Hadrian, for reasons given in that issue, we would need to store e.g mingw
under $topdir/../../mingw except for binary distributions, where we want
to follow the existing structure, in which case $topdir/../mingw is correct. So
we need to support both, which is what this patch hopefully implements.
  • Loading branch information
alpmestan committed Apr 16, 2018
1 parent fea04de commit 746b098
Show file tree
Hide file tree
Showing 3 changed files with 74 additions and 24 deletions.
16 changes: 8 additions & 8 deletions aclocal.m4
Original file line number Diff line number Diff line change
Expand Up @@ -470,15 +470,15 @@ AC_DEFUN([FP_SETTINGS],
if test "$windows" = YES -a "$EnableDistroToolchain" = "NO"
then
mingw_bin_prefix=mingw/bin/
SettingsCCompilerCommand="\$topdir/../${mingw_bin_prefix}gcc.exe"
SettingsHaskellCPPCommand="\$topdir/../${mingw_bin_prefix}gcc.exe"
SettingsCCompilerCommand="\$tooldir/${mingw_bin_prefix}gcc.exe"
SettingsHaskellCPPCommand="\$tooldir/${mingw_bin_prefix}gcc.exe"
SettingsHaskellCPPFlags="$HaskellCPPArgs"
SettingsLdCommand="\$topdir/../${mingw_bin_prefix}ld.exe"
SettingsArCommand="\$topdir/../${mingw_bin_prefix}ar.exe"
SettingsRanlibCommand="\$topdir/../${mingw_bin_prefix}ranlib.exe"
SettingsPerlCommand='$topdir/../perl/perl.exe'
SettingsDllWrapCommand="\$topdir/../${mingw_bin_prefix}dllwrap.exe"
SettingsWindresCommand="\$topdir/../${mingw_bin_prefix}windres.exe"
SettingsLdCommand="\$tooldir/${mingw_bin_prefix}ld.exe"
SettingsArCommand="\$tooldir/${mingw_bin_prefix}ar.exe"
SettingsRanlibCommand="\$tooldir/${mingw_bin_prefix}ranlib.exe"
SettingsPerlCommand='$tooldir/perl/perl.exe'
SettingsDllWrapCommand="\$tooldir/${mingw_bin_prefix}dllwrap.exe"
SettingsWindresCommand="\$tooldir/${mingw_bin_prefix}windres.exe"
SettingsTouchCommand='$topdir/bin/touchy.exe'
elif test "$EnableDistroToolchain" = "YES"
then
Expand Down
24 changes: 14 additions & 10 deletions compiler/main/SysTools.hs
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,8 @@ initSysTools mbMinusB
-- see Note [topdir: How GHC finds its files]
-- NB: top_dir is assumed to be in standard Unix
-- format, '/' separated
tool_dir <- findToolDir top_dir
-- see Note [tooldir: How GHC finds mingw and perl on Windows]

let settingsFile = top_dir </> "settings"
platformConstantsFile = top_dir </> "platformConstants"
Expand All @@ -158,6 +160,7 @@ initSysTools mbMinusB
let getSetting key = case lookup key mySettings of
Just xs -> return $ expandTopDir top_dir xs
Nothing -> pgmError ("No entry for " ++ show key ++ " in " ++ show settingsFile)
getToolSetting key = expandToolDir tool_dir <$> getSetting key
getBooleanSetting key = case lookup key mySettings of
Just "YES" -> return True
Just "NO" -> return False
Expand All @@ -179,14 +182,15 @@ initSysTools mbMinusB
targetHasSubsectionsViaSymbols <- readSetting "target has subsections via symbols"
myExtraGccViaCFlags <- getSetting "GCC extra via C opts"
-- On Windows, mingw is distributed with GHC,
-- so we look in TopDir/../mingw/bin
-- so we look in TopDir/../mingw/bin,
-- as well as TopDir/../../mingw/bin for hadrian.
-- It would perhaps be nice to be able to override this
-- with the settings file, but it would be a little fiddly
-- to make that possible, so for now you can't.
gcc_prog <- getSetting "C compiler command"
gcc_prog <- getToolSetting "C compiler command"
gcc_args_str <- getSetting "C compiler flags"
gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
cpp_prog <- getSetting "Haskell CPP command"
cpp_prog <- getToolSetting "Haskell CPP command"
cpp_args_str <- getSetting "Haskell CPP flags"
let unreg_gcc_args = if targetUnregisterised
then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
Expand All @@ -204,7 +208,7 @@ initSysTools mbMinusB
ldSupportsBuildId <- getBooleanSetting "ld supports build-id"
ldSupportsFilelist <- getBooleanSetting "ld supports filelist"
ldIsGnuLd <- getBooleanSetting "ld is GNU ld"
perl_path <- getSetting "perl command"
perl_path <- getToolSetting "perl command"

let pkgconfig_path = installed "package.conf.d"
ghc_usage_msg_path = installed "ghc-usage.txt"
Expand All @@ -217,14 +221,14 @@ initSysTools mbMinusB
-- split is a Perl script
split_script = libexec cGHC_SPLIT_PGM

windres_path <- getSetting "windres command"
libtool_path <- getSetting "libtool command"
ar_path <- getSetting "ar command"
ranlib_path <- getSetting "ranlib command"
windres_path <- getToolSetting "windres command"
libtool_path <- getToolSetting "libtool command"
ar_path <- getToolSetting "ar command"
ranlib_path <- getToolSetting "ranlib command"

tmpdir <- getTemporaryDirectory

touch_path <- getSetting "touch command"
touch_path <- getToolSetting "touch command"

let -- On Win32 we don't want to rely on #!/bin/perl, so we prepend
-- a call to Perl to get the invocation of split.
Expand All @@ -235,7 +239,7 @@ initSysTools mbMinusB
(split_prog, split_args)
| isWindowsHost = (perl_path, [Option split_script])
| otherwise = (split_script, [])
mkdll_prog <- getSetting "dllwrap command"
mkdll_prog <- getToolSetting "dllwrap command"
let mkdll_args = []

-- cpp is derived from gcc on all platforms
Expand Down
58 changes: 52 additions & 6 deletions compiler/main/SysTools/BaseDir.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,10 @@
-----------------------------------------------------------------------------
-}

module SysTools.BaseDir (expandTopDir, findTopDir) where
module SysTools.BaseDir
( expandTopDir, expandToolDir
, findTopDir, findToolDir
) where

#include "HsVersions.h"

Expand Down Expand Up @@ -70,16 +73,41 @@ On Windows:
from topdir we can find package.conf, ghc-asm, etc.
Note [tooldir: How GHC finds mingw and perl on Windows]
GHC has some custom logic on Windows for finding the mingw
toolchain and perl. Depending on whether GHC is built
with the make build system or Hadrian, and on whether we're
running a bindist, we might find the mingw toolchain and perl
either under $topdir/../{mingw, perl}/ or
$topdir/../../{mingw, perl}/.
-}

-- | Expand occurrences of the @$topdir@ interpolation in a string.
expandTopDir :: FilePath -> String -> String
expandTopDir top_dir str
| Just str' <- stripPrefix "$topdir" str
expandTopDir = expandPathVar "topdir"

-- | Expand occurrences of the @$tooldir@ interpolation in a string
-- on Windows, leave the string untouched otherwise.
expandToolDir :: FilePath -> String -> String
#if defined(mingw32_HOST_OS)
expandToolDir = expandPathVar "tooldir"
#else
expandToolDir _ s = s
#endif

-- | @expandPathVar var value str@
--
-- replaces occurences of variable @$var@ with @value@ in str.
expandPathVar :: String -> FilePath -> String -> String
expandPathVar var value str
| Just str' <- stripPrefix ('$':var) str
, null str' || isPathSeparator (head str')
= top_dir ++ expandTopDir top_dir str'
expandTopDir top_dir (x:xs) = x : expandTopDir top_dir xs
expandTopDir _ [] = []
= value ++ expandPathVar var value str'
expandPathVar var value (x:xs) = x : expandPathVar var value xs
expandPathVar _ _ [] = []

-- | Returns a Unix-format path pointing to TopDir.
findTopDir :: Maybe String -- Maybe TopDir path (without the '-B' prefix).
Expand Down Expand Up @@ -193,3 +221,21 @@ getBaseDir = Just . (\p -> p </> "lib") . takeDirectory . takeDirectory <$> getE
#else
getBaseDir = return Nothing
#endif

-- See Note [tooldir: How GHC finds mingw and perl on Windows]
findToolDir
:: FilePath -- ^ topdir
-> IO FilePath
#if defined(mingw32_HOST_OS)
findToolDir top_dir = go 0 (top_dir </> "..")
where maxDepth = 2
go k path
| k == maxDepth = throwGhcExceptionIO (InstallationError "could not detect mingw toolchain")
| otherwise = do
oneLevel <- doesDirectoryExist (path </> "mingw")
if oneLevel
then return path
else go (k+1) (path </> "..")
#else
findToolDir = panic "getToolDir should only be called on Windows"
#endif

0 comments on commit 746b098

Please sign in to comment.