diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index 1d77a19e7f67..5d15c8102532 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -278,7 +278,7 @@ import GHC.Core.Opt.CallerCC import GHC.Parser (parseIdentifier) import GHC.Parser.Lexer (mkParserOpts, initParserState, P(..), ParseResult(..)) -import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir ) +import GHC.SysTools.BaseDir ( expandTopDir ) import Data.IORef import Control.Arrow ((&&&)) @@ -3465,7 +3465,7 @@ compilerInfo dflags -- Next come the settings, so anything else can be overridden -- in the settings file (as "lookup" uses the first match for the -- key) - : map (fmap $ expandDirectories (topDir dflags) (toolDir dflags)) + : map (fmap $ expandTopDir (topDir dflags)) (rawSettings dflags) ++ [("Project version", projectVersion dflags), ("Edition", "Stable Haskell"), @@ -3525,9 +3525,6 @@ compilerInfo dflags showBool False = "NO" platform = targetPlatform dflags isWindows = platformOS platform == OSMinGW32 - useInplaceMinGW = toolSettings_useInplaceMinGW $ toolSettings dflags - expandDirectories :: FilePath -> Maybe FilePath -> String -> String - expandDirectories topd mtoold = expandToolDir useInplaceMinGW mtoold . expandTopDir topd -- Note [Special unit-ids] -- ~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/GHC/Settings/IO.hs b/compiler/GHC/Settings/IO.hs index 63964ff02ff8..b5e949ff18aa 100644 --- a/compiler/GHC/Settings/IO.hs +++ b/compiler/GHC/Settings/IO.hs @@ -69,28 +69,23 @@ initSettings top_dir = do -- see Note [topdir: How GHC finds its files] -- NB: top_dir is assumed to be in standard Unix -- format, '/' separated - mtool_dir <- liftIO $ findToolDir useInplaceMinGW top_dir - -- see Note [tooldir: How GHC finds mingw on Windows] - -- Escape 'top_dir' and 'mtool_dir', to make sure we don't accidentally + -- Escape 'top_dir' to make sure we don't accidentally -- introduce unescaped spaces. See #24265 and #25204. let escaped_top_dir = escapeArg top_dir - escaped_mtool_dir = fmap escapeArg mtool_dir getSetting_raw key = either pgmError pure $ getRawSetting settingsFile mySettings key getSetting_topDir top key = either pgmError pure $ getRawFilePathSetting top settingsFile mySettings key - getSetting_toolDir top tool key = - expandToolDir useInplaceMinGW tool <$> getSetting_topDir top key getSetting :: String -> ExceptT SettingsError m String getSetting key = getSetting_topDir top_dir key getToolSetting :: String -> ExceptT SettingsError m String - getToolSetting key = getSetting_toolDir top_dir mtool_dir key + getToolSetting key = getSetting_topDir top_dir key getFlagsSetting :: String -> ExceptT SettingsError m [String] - getFlagsSetting key = unescapeArgs <$> getSetting_toolDir escaped_top_dir escaped_mtool_dir key - -- Make sure to unescape, as we have escaped top_dir and tool_dir. + getFlagsSetting key = unescapeArgs <$> getSetting_topDir escaped_top_dir key + -- Make sure to unescape, as we have escaped top_dir. -- See Note [Settings file] for a little more about this file. We're -- just partially applying those functions and throwing 'Left's; they're @@ -196,7 +191,7 @@ initSettings top_dir = do , sFileSettings = FileSettings { fileSettings_ghcUsagePath = ghc_usage_msg_path , fileSettings_ghciUsagePath = ghci_usage_msg_path - , fileSettings_toolDir = mtool_dir + , fileSettings_toolDir = Nothing , fileSettings_topDir = top_dir , fileSettings_globalPackageDatabase = globalpkgdb_path } diff --git a/compiler/GHC/SysTools/BaseDir.hs b/compiler/GHC/SysTools/BaseDir.hs index bbbe0913e438..e3c8628cb027 100644 --- a/compiler/GHC/SysTools/BaseDir.hs +++ b/compiler/GHC/SysTools/BaseDir.hs @@ -12,8 +12,8 @@ -} module GHC.SysTools.BaseDir - ( expandTopDir, expandToolDir - , findTopDir, findToolDir + ( expandTopDir + , findTopDir , tryFindTopDir ) where @@ -27,11 +27,6 @@ import GHC.Utils.Panic import System.Environment (lookupEnv) import System.FilePath --- Windows -#if defined(mingw32_HOST_OS) -import System.Directory (doesDirectoryExist) -#endif - {- Note [topdir: How GHC finds its files] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -119,14 +114,6 @@ provide the override which allows GHC to instead of using an inplace compiler to play nice with the system compiler instead. -} --- | Expand occurrences of the @$tooldir@ interpolation in a string --- on Windows, leave the string untouched otherwise. -expandToolDir - :: Bool -- ^ whether we use the ambient mingw toolchain - -> Maybe FilePath -- ^ tooldir - -> String -> String -expandToolDir _ _ s = s - -- | Returns a Unix-format path pointing to TopDir. findTopDir :: Maybe String -- Maybe TopDir path (without the '-B' prefix). -> IO String -- TopDir (in Unix format '/' separated) @@ -152,15 +139,3 @@ tryFindTopDir Nothing Just env_top_dir -> return $ Just env_top_dir -- Try directory of executable Nothing -> getBaseDir - - --- See Note [tooldir: How GHC finds mingw on Windows] --- Returns @Nothing@ when not on Windows. --- When called on Windows, it either throws an error when the --- tooldir can't be located, or returns @Just tooldirpath@. --- If the distro toolchain is being used we treat Windows the same as Linux -findToolDir - :: Bool -- ^ whether we use the ambient mingw toolchain - -> FilePath -- ^ topdir - -> IO (Maybe FilePath) -findToolDir _ _ = return Nothing diff --git a/testsuite/tests/codeGen/should_run/T25374/all.T b/testsuite/tests/codeGen/should_run/T25374/all.T index 3676ebc33da6..0e02dc0d263d 100644 --- a/testsuite/tests/codeGen/should_run/T25374/all.T +++ b/testsuite/tests/codeGen/should_run/T25374/all.T @@ -1,3 +1,3 @@ # This shouldn't crash the disassembler -test('T25374', [fragile(0), extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, req_target_debug_rts], ghci_script, ['']) +test('T25374', [extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, req_target_debug_rts], ghci_script, ['']) diff --git a/testsuite/tests/ghci/linking/T25240/all.T b/testsuite/tests/ghci/linking/T25240/all.T index 0083c227772b..d5cf63c3597f 100644 --- a/testsuite/tests/ghci/linking/T25240/all.T +++ b/testsuite/tests/ghci/linking/T25240/all.T @@ -1,3 +1,3 @@ # skip on darwin because the leading underscores will make the test fail -test('T25240', [when(leading_underscore(),skip), fragile(0), req_interp, extra_files(['T25240a.hs'])], +test('T25240', [when(leading_underscore(),skip), req_interp, extra_files(['T25240a.hs'])], makefile_test, ['T25240']) diff --git a/testsuite/tests/rts/T23142.hs b/testsuite/tests/rts/T23142.hs index 0e667470c26d..75e255c68fb2 100644 --- a/testsuite/tests/rts/T23142.hs +++ b/testsuite/tests/rts/T23142.hs @@ -1,5 +1,5 @@ {-# LANGUAGE UnboxedTuples, MagicHash #-} -module Main where +module T23142 where import GHC.IO import GHC.Exts diff --git a/testsuite/tests/rts/linker/T20494-obj.c b/testsuite/tests/rts/linker/T20494-obj.c index a792993aa154..ed073d6cfaf0 100644 --- a/testsuite/tests/rts/linker/T20494-obj.c +++ b/testsuite/tests/rts/linker/T20494-obj.c @@ -1,15 +1,8 @@ #include -#include #define CONSTRUCTOR(prio) __attribute__((constructor(prio))) #define DESTRUCTOR(prio) __attribute__((destructor(prio))) -#if defined(_WIN32) #define PRINT(str) printf(str); fflush(stdout) -#else -// don't use "stdout" variable here as it is not properly defined when loading -// this object in a statically linked GHC. -#define PRINT(str) dprintf(1,str); fsync(1) -#endif CONSTRUCTOR(1000) void constr_a(void) { PRINT("constr a\n"); } CONSTRUCTOR(2000) void constr_b(void) { PRINT("constr b\n"); }