diff --git a/hadrian/src/Builder.hs b/hadrian/src/Builder.hs
index 5b8056e13929e56e4da30aba7cd31bda74ec241f..581161f984e75fa492378a0c647aa3399bc762ab 100644
--- a/hadrian/src/Builder.hs
+++ b/hadrian/src/Builder.hs
@@ -28,7 +28,6 @@ import Hadrian.Utilities
 import Base
 import Context
 import Oracles.Flag
-import Oracles.Setting
 import Packages
 
 -- | C compiler can be used in two different modes:
@@ -179,7 +178,6 @@ instance H.Builder Builder where
         Ghc _ Stage0 -> generatedGhcDependencies Stage0
         Ghc _ stage -> do
             root <- buildRoot
-            win <- windowsHost
             touchyPath <- programPath (vanillaContext Stage0 touchy)
             unlitPath  <- builderPath Unlit
             ghcgens <- generatedGhcDependencies stage
@@ -191,8 +189,8 @@ instance H.Builder Builder where
             return $ [ unlitPath ]
                   ++ ghcdeps
                   ++ ghcgens
-                  ++ [ touchyPath | win ]
-                  ++ [ root -/- mingwStamp | win ]
+                  ++ [ touchyPath          | windowsHost ]
+                  ++ [ root -/- mingwStamp | windowsHost ]
                      -- proxy for the entire mingw toolchain that
                      -- we have in inplace/mingw initially, and then at
                      -- root -/- mingw.
@@ -331,9 +329,8 @@ systemBuilderPath builder = case builder of
                 ++ quote key ++ " is not specified" ++ inCfg
             return "" -- TODO: Use a safe interface.
         else do
-            win <- windowsHost
             fullPath <- lookupInPath path
-            case (win, hasExtension fullPath) of
+            case (windowsHost, hasExtension fullPath) of
                 (False, _    ) -> return fullPath
                 (True , True ) -> fixAbsolutePathOnWindows fullPath
                 (True , False) -> fixAbsolutePathOnWindows fullPath <&> (<.> exe)
diff --git a/hadrian/src/Hadrian/Builder/Tar.hs b/hadrian/src/Hadrian/Builder/Tar.hs
index 1d8f5025a5b7bd75a0f4cd620dfc8ad0e8e19f2c..5b145a7127cb805220328357d22f20aa66261585 100644
--- a/hadrian/src/Hadrian/Builder/Tar.hs
+++ b/hadrian/src/Hadrian/Builder/Tar.hs
@@ -14,7 +14,7 @@ import Development.Shake
 import Development.Shake.Classes
 import GHC.Generics
 import Hadrian.Expression
-import Oracles.Setting
+import Hadrian.Utilities
 
 -- | Tar can be used to 'Create' an archive or 'Extract' from it.
 data TarMode = Create | Extract deriving (Eq, Generic, Show)
diff --git a/hadrian/src/Hadrian/Utilities.hs b/hadrian/src/Hadrian/Utilities.hs
index 48ba34964e8959e6c4fd2f2a37cd02cdd5a6f4f3..c934fa259d65b017b1a381ed101c24031ed45994 100644
--- a/hadrian/src/Hadrian/Utilities.hs
+++ b/hadrian/src/Hadrian/Utilities.hs
@@ -28,7 +28,7 @@ module Hadrian.Utilities (
     renderAction, renderActionNoOutput, renderProgram, renderLibrary, renderBox, renderUnicorn,
 
     -- * Miscellaneous
-    (<&>), (%%>), cmdLineLengthLimit,
+    (<&>), (%%>), cmdLineLengthLimit, windowsHost, osxHost, iosHost,
 
     -- * Useful re-exports
     Dynamic, fromDynamic, toDyn, TypeRep, typeOf
@@ -47,7 +47,6 @@ import Development.Shake hiding (Normal)
 import Development.Shake.Classes
 import Development.Shake.FilePath
 import System.Environment (lookupEnv)
-import System.Info.Extra
 
 import qualified Control.Exception.Base as IO
 import qualified Data.HashMap.Strict    as Map
@@ -231,9 +230,21 @@ infix 1 %%>
 -- 20000. Hence, 200000 seems like a sensible limit. On other operating systems
 -- we currently use the 4194304 setting.
 cmdLineLengthLimit :: Int
-cmdLineLengthLimit | isWindows = 31000
-                   | isMac     = 200000
-                   | otherwise = 4194304
+cmdLineLengthLimit | IO.isWindows = 31000
+                   | IO.isMac     = 200000
+                   | otherwise    = 4194304
+
+-- | Check if the host OS is Windows.
+windowsHost :: Bool
+windowsHost = IO.isWindows
+
+-- | Check if the host OS is Mac OS.
+osxHost :: Bool
+osxHost = IO.isMac
+
+-- | Check if the host OS is iOS.
+iosHost :: Bool
+iosHost = IO.os == "ios"
 
 -- | Insert a value into Shake's type-indexed map.
 insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic
diff --git a/hadrian/src/Oracles/Setting.hs b/hadrian/src/Oracles/Setting.hs
index 89f5d70c9f8b0428935843d1203dbcbc53d8119a..408f9e342257c0fc40b8c3b53b8c44b37b2b9b9c 100644
--- a/hadrian/src/Oracles/Setting.hs
+++ b/hadrian/src/Oracles/Setting.hs
@@ -2,10 +2,8 @@ module Oracles.Setting (
     configFile, Setting (..), SettingList (..), setting, settingList, getSetting,
     getSettingList,  anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs,
     ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors,
-    ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost,
-    hostSupportsRPaths, topDirectory, libsuf, ghcVersionStage,
-    SettingsFileSetting (..),
-    settingsFileSetting
+    ghcCanonVersion, cmdLineLengthLimit, hostSupportsRPaths, topDirectory,
+    libsuf, ghcVersionStage, SettingsFileSetting (..), settingsFileSetting
     ) where
 
 import Hadrian.Expression
@@ -209,14 +207,6 @@ anyTargetArch = matchSetting TargetArch
 anyHostOs :: [String] -> Action Bool
 anyHostOs = matchSetting HostOs
 
--- | Check whether the host OS setting is set to @"ios"@.
-iosHost :: Action Bool
-iosHost = anyHostOs ["ios"]
-
--- | Check whether the host OS setting is set to @"darwin"@.
-osxHost :: Action Bool
-osxHost = anyHostOs ["darwin"]
-
 -- | Check whether the host OS supports the @-rpath@ linker option when
 -- using dynamic linking.
 --
@@ -225,10 +215,6 @@ osxHost = anyHostOs ["darwin"]
 hostSupportsRPaths :: Action Bool
 hostSupportsRPaths = anyHostOs ["linux", "darwin", "freebsd"]
 
--- | Check whether the host OS setting is set to @"mingw32"@ or @"cygwin32"@.
-windowsHost :: Action Bool
-windowsHost = anyHostOs ["mingw32", "cygwin32"]
-
 -- | Check whether the target supports GHCi.
 ghcWithInterpreter :: Action Bool
 ghcWithInterpreter = do
diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs
index f5e3a64df5e5fa1ac7a1e0bee75a5236c72266d4..8bb86a63332825191fdc617ad1891a8de3146782 100644
--- a/hadrian/src/Packages.hs
+++ b/hadrian/src/Packages.hs
@@ -212,8 +212,7 @@ libffiBuildPath stage = buildPath $ Context
 libffiLibraryName :: Action FilePath
 libffiLibraryName = do
     useSystemFfi <- flag UseSystemFfi
-    windows      <- windowsHost
-    return $ case (useSystemFfi, windows) of
+    return $ case (useSystemFfi, windowsHost) of
         (True , False) -> "ffi"
         (False, False) -> "Cffi"
         (_    , True ) -> "Cffi-6"
diff --git a/hadrian/src/Rules/BinaryDist.hs b/hadrian/src/Rules/BinaryDist.hs
index 9f5aba84019b33b96b922508c025e1b22c2b47d9..11301a03723f6f1963bc26b36ba09229c445f158 100644
--- a/hadrian/src/Rules/BinaryDist.hs
+++ b/hadrian/src/Rules/BinaryDist.hs
@@ -107,7 +107,6 @@ bindistRules = do
         targetPlatform <- setting TargetPlatformFull
         distDir        <- Context.distDir Stage1
         rtsDir         <- pkgIdentifier rts
-        windows        <- windowsHost
 
         let ghcBuildDir      = root -/- stageString Stage1
             bindistFilesDir  = root -/- "bindist" -/- ghcVersionPretty
@@ -129,7 +128,7 @@ bindistRules = do
         -- contain outdated or even invalid data.
         whenM (doesDirectoryExist (root -/- "docs")) $ do
           copyDirectory (root -/- "docs") bindistFilesDir
-        when windows $ do
+        when windowsHost $ do
           copyDirectory (root -/- "mingw") bindistFilesDir
           -- we use that opportunity to delete the .stamp file that we use
           -- as a proxy for the whole mingw toolchain, there's no point in
@@ -283,8 +282,7 @@ ghciScriptWrapper = unlines
 --   explicitly and 'need' the result of building them.
 needIservBins :: Action ()
 needIservBins = do
-    windows <- windowsHost
-    when (not windows) $ do
+    when (not windowsHost) $ do
         rtsways <- interpretInContext (vanillaContext Stage1 ghc) getRtsWays
         need =<< traverse programPath
                    [ Context Stage1 iserv w
diff --git a/hadrian/src/Rules/Configure.hs b/hadrian/src/Rules/Configure.hs
index ba67df20a6d47553981b9c1fa227e4f483d4ab93..fd56b4511a58059b0b3bc4cc33a0ec698617ea60 100644
--- a/hadrian/src/Rules/Configure.hs
+++ b/hadrian/src/Rules/Configure.hs
@@ -27,7 +27,7 @@ configureRules = do
                 ++ "automatically by passing the flag --configure."
         else do
             -- We cannot use windowsHost here due to a cyclic dependency.
-            when System.isWindows $ do
+            when windowsHost $ do
                 putBuild "| Checking for Windows tarballs..."
                 quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch]
             let srcs    = map (<.> "in") outs
@@ -39,7 +39,7 @@ configureRules = do
             -- We need to copy the directory with unpacked Windows tarball to
             -- the build directory, so that the built GHC has access to it.
             -- See https://github.com/snowleopard/hadrian/issues/564.
-            when System.isWindows $ do
+            when windowsHost $ do
                 root <- buildRoot
                 copyDirectory "inplace/mingw" (root -/- "mingw")
                 mingwFiles <- liftIO $ getDirectoryFilesIO "." [root -/- "mingw/**"]
diff --git a/hadrian/src/Rules/Gmp.hs b/hadrian/src/Rules/Gmp.hs
index 5666ab39052514d85cba0a14308b6dd6b511f1c2..61fb4125d3870042851a70e870c8272818f74355 100644
--- a/hadrian/src/Rules/Gmp.hs
+++ b/hadrian/src/Rules/Gmp.hs
@@ -61,9 +61,8 @@ gmpRules = do
     -- Copy appropriate GMP header and object files
     gmpPath <- gmpBuildPathRules
     gmpPath -/- gmpLibraryH %> \header -> do
-        windows  <- windowsHost
         configMk <- readFile' =<< (buildPath gmpContext <&> (-/- "config.mk"))
-        if not windows && -- TODO: We don't use system GMP on Windows. Fix?
+        if not windowsHost && -- TODO: We don't use system GMP on Windows. Fix?
            any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ]
         then do
             putBuild "| GMP library/framework detected and will be used"
diff --git a/hadrian/src/Rules/Libffi.hs b/hadrian/src/Rules/Libffi.hs
index e3f080dda12f7c2f6be5992437fd13e89fb1dc4e..ebd6cef849a538da49e3c2a597cb597f3d223916 100644
--- a/hadrian/src/Rules/Libffi.hs
+++ b/hadrian/src/Rules/Libffi.hs
@@ -84,15 +84,13 @@ libffiContext stage = do
 -- | The name of the (locally built) library
 libffiName :: Expr String
 libffiName = do
-    windows <- expr windowsHost
     way <- getWay
-    return $ libffiName' windows (Dynamic `wayUnit` way)
+    return $ libffiName' (Dynamic `wayUnit` way)
 
 -- | The name of the (locally built) library
-libffiName' :: Bool -> Bool -> String
-libffiName' windows dynamic
-    = (if dynamic then "" else "C")
-    ++ (if windows then "ffi-6" else "ffi")
+libffiName' :: Bool -> String
+libffiName' dynamic = (if dynamic     then ""      else "C")
+                   ++ (if windowsHost then "ffi-6" else "ffi")
 
 libffiLibrary :: FilePath
 libffiLibrary = "inst/lib/libffi.a"
@@ -169,15 +167,13 @@ libffiRules = do
 
         -- Find dynamic libraries.
         dynLibFiles <- do
-            windows <- windowsHost
-            osx     <- osxHost
             let libfilesDir = libffiPath -/-
-                    (if windows then "inst" -/- "bin" else "inst" -/- "lib")
-                libffiName'' = libffiName' windows True
+                    (if windowsHost then "inst" -/- "bin" else "inst" -/- "lib")
+                libffiName'' = libffiName' True
                 dynlibext
-                    | windows   = "dll"
-                    | osx       = "dylib"
-                    | otherwise = "so"
+                    | windowsHost = "dll"
+                    | osxHost     = "dylib"
+                    | otherwise   = "so"
                 filepat = "lib" ++ libffiName'' ++ "." ++ dynlibext ++ "*"
             liftIO $ getDirectoryFilesIO "." [libfilesDir -/- filepat]
 
diff --git a/hadrian/src/Rules/Register.hs b/hadrian/src/Rules/Register.hs
index d815d40c985942e1b0110d07e3a65a0682a65b06..b6acf566f7ef854eebb403b6330273447e9b6ce5 100644
--- a/hadrian/src/Rules/Register.hs
+++ b/hadrian/src/Rules/Register.hs
@@ -137,12 +137,11 @@ buildConf _ context@Context {..} conf = do
     -- to record this side effect so that Shake can cache these files too.
     -- See why we need 'fixWindows': https://gitlab.haskell.org/ghc/ghc/issues/16073
     let fixWindows path = do
-            win <- windowsHost
             version  <- setting GhcVersion
             hostOs   <- cabalOsString <$> setting BuildOs
             hostArch <- cabalArchString <$> setting BuildArch
             let dir = hostArch ++ "-" ++ hostOs ++ "-ghc-" ++ version
-            return $ if win then path -/- "../.." -/- dir else path
+            return $ if windowsHost then path -/- "../.." -/- dir else path
     pkgDbPath <- fixWindows =<< packageDbPath stage
     let dir = pkgDbPath -/- takeBaseName conf
     files <- liftIO $ getDirectoryFilesIO "." [dir -/- "**"]
diff --git a/hadrian/src/Rules/Rts.hs b/hadrian/src/Rules/Rts.hs
index c9669f520da69e9161dc60ae8d9221e6c36846e1..64864eee82eedc4412029d207cb033d0385e647e 100644
--- a/hadrian/src/Rules/Rts.hs
+++ b/hadrian/src/Rules/Rts.hs
@@ -83,8 +83,7 @@ copyLibffiDynamicUnix stage libSuf target = do
         copyFile' versionlessSourceFilePath target
 
         -- On OSX the dylib's id must be updated to a relative path.
-        osx <- osxHost
-        when osx $ cmd
+        when osxHost $ cmd
             [ "install_name_tool"
             , "-id", "@rpath/" ++ takeFileName target
             , target
diff --git a/hadrian/src/Rules/Selftest.hs b/hadrian/src/Rules/Selftest.hs
index b931f85ef6ee4d26eaf243f10450f409e1c3ce8c..bd7e5f954450c4a6dd2fd89c4a3def8b76e00103 100644
--- a/hadrian/src/Rules/Selftest.hs
+++ b/hadrian/src/Rules/Selftest.hs
@@ -7,7 +7,6 @@ import Test.QuickCheck
 import Base
 import Context
 import Oracles.ModuleFiles
-import Oracles.Setting
 import Packages
 import Settings
 import Target
@@ -102,12 +101,11 @@ testModuleName = do
 testPackages :: Action ()
 testPackages = do
     putBuild "==== Check system configuration"
-    win <- windowsHost -- This depends on the @boot@ and @configure@ scripts.
     putBuild "==== Packages, interpretInContext, configuration flags"
     forM_ [Stage0 ..] $ \stage -> do
         pkgs <- stagePackages stage
-        when (win32 `elem` pkgs) . test $ win
-        when (unix  `elem` pkgs) . test $ not win
+        when (win32 `elem` pkgs) . test $ windowsHost
+        when (unix  `elem` pkgs) . test $ not windowsHost
         test $ pkgs == nubOrd pkgs
 
 testWay :: Action ()
diff --git a/hadrian/src/Rules/Test.hs b/hadrian/src/Rules/Test.hs
index f5d0dd53b67ae99d00cc827518a6d4e3d7c63751..23352ed2607aad3b284da935a5d57fb6ea7769ef 100644
--- a/hadrian/src/Rules/Test.hs
+++ b/hadrian/src/Rules/Test.hs
@@ -135,8 +135,7 @@ testRules = do
 timeoutProgBuilder :: Action ()
 timeoutProgBuilder = do
     root    <- buildRoot
-    windows <- windowsHost
-    if windows
+    if windowsHost
         then do
             prog <- programPath =<< programContext Stage1 timeout
             copyFile prog (root -/- timeoutPath)
@@ -178,8 +177,7 @@ stageOf _ = error "unexpected stage argument"
 needIservBins :: Action ()
 needIservBins = do
     -- iserv is not supported under Windows
-    windows <- windowsHost
-    when (not windows) $ do
+    when (not windowsHost) $ do
         testGhc <- testCompiler <$> userSetting defaultTestArgs
         let stg = stageOf testGhc
         rtsways <- interpretInContext (vanillaContext stg ghc) getRtsWays
diff --git a/hadrian/src/Settings/Builders/Cabal.hs b/hadrian/src/Settings/Builders/Cabal.hs
index e759206029394bd74ffbe0c257c356c05ac58065..759c0fde58dd2cfaf10e0e08290fba817f8e07e9 100644
--- a/hadrian/src/Settings/Builders/Cabal.hs
+++ b/hadrian/src/Settings/Builders/Cabal.hs
@@ -16,8 +16,7 @@ cabalBuilderArgs = builder (Cabal Setup) ? do
     pkg       <- getPackage
     path      <- getContextPath
     stage     <- getStage
-    windows   <- expr windowsHost
-    let prefix = "${pkgroot}" ++ (if windows then "" else "/..")
+    let prefix = "${pkgroot}" ++ (if windowsHost then "" else "/..")
     mconcat [ arg "configure"
             -- Don't strip libraries when cross compiling.
             -- TODO: We need to set @--with-strip=(stripCmdPath :: Action FilePath)@,
diff --git a/hadrian/src/Settings/Builders/Common.hs b/hadrian/src/Settings/Builders/Common.hs
index cfe09112925fc3ec042876c1d650ae14ded8f06a..5856935fb99cdb30253e2751eea8d050d513a040 100644
--- a/hadrian/src/Settings/Builders/Common.hs
+++ b/hadrian/src/Settings/Builders/Common.hs
@@ -53,7 +53,7 @@ cWarnings :: Args
 cWarnings = mconcat
     [ arg "-Wall"
     , flag GccIsClang ? arg "-Wno-unknown-pragmas"
-    , notM (flag GccIsClang) ? notM windowsHost ? arg "-Werror=unused-but-set-variable"
+    , notM (flag GccIsClang) ? not windowsHost ? arg "-Werror=unused-but-set-variable"
     , notM (flag GccIsClang) ? arg "-Wno-error=inline" ]
 
 packageDatabaseArgs :: Args
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index 99165fba06bdc8d973fa50ccb5746a3deb90ff33..2db62aa4e1dc76bbd47723ce30802e0722f65bf0 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -61,7 +61,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
     libs    <- getContextData extraLibs
     libDirs <- getContextData extraLibDirs
     fmwks   <- getContextData frameworks
-    darwin  <- expr osxHost
     way     <- getWay
 
     -- Relative path from the output (rpath $ORIGIN).
@@ -87,7 +86,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
             -- libraries will all end up in the lib dir, so just use $ORIGIN
             | otherwise     = metaOrigin
             where
-                metaOrigin | darwin    = "@loader_path"
+                metaOrigin | osxHost   = "@loader_path"
                            | otherwise = "$ORIGIN"
 
         -- TODO: an alternative would be to generalize by linking with extra
@@ -117,7 +116,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
                       [ arg ("-optl-Wl,-rpath," ++ rpath)
                       , isProgram pkg ? arg ("-optl-Wl,-rpath," ++ bindistRpath)
                       -- The darwin linker doesn't support/require the -zorigin option
-                      , not darwin ? arg "-optl-Wl,-zorigin"
+                      , not osxHost ? arg "-optl-Wl,-zorigin"
                       ]
                 ]
             , arg "-no-auto-link-packages"
@@ -126,7 +125,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
             , pure [ "-l" ++ lib    | lib    <- libs    ]
             , pure [ "-L" ++ libDir | libDir <- libDirs ]
             , rtsFfiArg
-            , darwin ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ])
+            , osxHost ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ])
             , debugged ? packageOneOf [ghc, iservProxy, iserv, remoteIserv] ?
               arg "-debug"
 
diff --git a/hadrian/src/Settings/Builders/Hsc2Hs.hs b/hadrian/src/Settings/Builders/Hsc2Hs.hs
index e2b9e4426064f1f6b90fdf0bcbd16fd6228cda34..67c32c5ed4d575fae3bb5b40a1ab16b5ff6732bb 100644
--- a/hadrian/src/Settings/Builders/Hsc2Hs.hs
+++ b/hadrian/src/Settings/Builders/Hsc2Hs.hs
@@ -22,7 +22,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do
     tmpl <- (top -/-) <$> expr (templateHscPath Stage0)
     mconcat [ arg $ "--cc=" ++ ccPath
             , arg $ "--ld=" ++ ccPath
-            , notM windowsHost ? notM (flag CrossCompiling) ? arg "--cross-safe"
+            , not windowsHost ? notM (flag CrossCompiling) ? arg "--cross-safe"
             , pure $ map ("-I" ++) (words gmpDir)
             , map ("--cflag=" ++) <$> getCFlags
             , map ("--lflag=" ++) <$> getLFlags
diff --git a/hadrian/src/Settings/Builders/RunTest.hs b/hadrian/src/Settings/Builders/RunTest.hs
index 63e3dfd6c951db80ba94e718ed6e75941b8b1b71..ff35d9573780fe838efd881acc91e3358cbb1343 100644
--- a/hadrian/src/Settings/Builders/RunTest.hs
+++ b/hadrian/src/Settings/Builders/RunTest.hs
@@ -76,8 +76,6 @@ runTestBuilderArgs = builder RunTest ? do
         (,) <$> (maybe False (=="YES") <$> lookupEnv "PLATFORM")
             <*> (maybe False (=="YES") <$> lookupEnv "OS")
 
-    windows     <- expr windowsHost
-    darwin      <- expr osxHost
     threads     <- shakeThreads <$> expr getShakeOptions
     os          <- getTestSetting TestHostOS
     arch        <- getTestSetting TestTargetARCH_CPP
@@ -101,8 +99,8 @@ runTestBuilderArgs = builder RunTest ? do
     -- TODO: set CABAL_MINIMAL_BUILD/CABAL_PLUGIN_BUILD
     mconcat [ arg $ "testsuite/driver/runtests.py"
             , pure [ "--rootdir=" ++ testdir | testdir <- rootdirs ]
-            , arg "-e", arg $ "windows=" ++ show windows
-            , arg "-e", arg $ "darwin=" ++ show darwin
+            , arg "-e", arg $ "windows=" ++ show windowsHost
+            , arg "-e", arg $ "darwin=" ++ show osxHost
             , arg "-e", arg $ "config.local=False"
             , arg "-e", arg $ "config.cleanup=" ++ show (not keepFiles)
             , arg "-e", arg $ "config.accept=" ++ show accept
diff --git a/hadrian/src/Settings/Default.hs b/hadrian/src/Settings/Default.hs
index 16e63fb04b7e5bcc33dbd75e0ed837a19e39ab6b..5963a7687c32f86cdd27963159109543efda8643 100644
--- a/hadrian/src/Settings/Default.hs
+++ b/hadrian/src/Settings/Default.hs
@@ -22,7 +22,6 @@ import CommandLine
 import Expression
 import Flavour
 import Oracles.Flag
-import Oracles.Setting
 import Packages
 import Settings
 import Settings.Builders.Alex
@@ -54,7 +53,6 @@ defaultPackages Stage3 = return []
 -- | Packages built in 'Stage0' by default. You can change this in "UserSettings".
 stage0Packages :: Action [Package]
 stage0Packages = do
-    win <- windowsHost
     cross <- flag CrossCompiling
     return $ [ binary
              , cabal
@@ -77,13 +75,12 @@ stage0Packages = do
              , text
              , transformers
              , unlit                         ]
-          ++ [ terminfo | not win, not cross ]
-          ++ [ touchy   | win                ]
+          ++ [ terminfo | not windowsHost, not cross ]
+          ++ [ touchy   | windowsHost                ]
 
 -- | Packages built in 'Stage1' by default. You can change this in "UserSettings".
 stage1Packages :: Action [Package]
 stage1Packages = do
-    win        <- windowsHost
     intLib     <- integerLibrary =<< flavour
     libraries0 <- filter isLibrary <$> stage0Packages
     cross      <- flag CrossCompiling
@@ -111,14 +108,14 @@ stage1Packages = do
              , unlit
              , xhtml
              ]
-          ++ [ haddock | not cross           ]
-          ++ [ hpcBin   | not cross          ]
-          ++ [ iserv    | not win, not cross ]
-          ++ [ libiserv | not win, not cross ]
-          ++ [ runGhc   | not cross          ]
-          ++ [ touchy   | win                ]
-          ++ [ unix     | not win            ]
-          ++ [ win32    | win                ]
+          ++ [ haddock  | not cross                  ]
+          ++ [ hpcBin   | not cross                  ]
+          ++ [ iserv    | not windowsHost, not cross ]
+          ++ [ libiserv | not windowsHost, not cross ]
+          ++ [ runGhc   | not cross                  ]
+          ++ [ touchy   | windowsHost                ]
+          ++ [ unix     | not windowsHost            ]
+          ++ [ win32    | windowsHost                ]
 
 -- | Packages built in 'Stage2' by default. You can change this in "UserSettings".
 stage2Packages :: Action [Package]
@@ -127,7 +124,6 @@ stage2Packages = stage1Packages
 -- | Packages that are built only for the testsuite.
 testsuitePackages :: Action [Package]
 testsuitePackages = do
-    win <- windowsHost
     return $ [ checkApiAnnotations
              , checkPpr
              , ghci
@@ -137,8 +133,8 @@ testsuitePackages = do
              , hsc2hs
              , iserv
              , runGhc
-             , unlit         ] ++
-             [ timeout | win ]
+             , unlit                 ] ++
+             [ timeout | windowsHost ]
 
 -- | Default build ways for library packages:
 -- * We always build 'vanilla' way.
@@ -227,9 +223,8 @@ defaultFlavour = Flavour
 --   in @mk/config.mk.in@.
 defaultDynamicGhcPrograms :: Action Bool
 defaultDynamicGhcPrograms = do
-  win <- windowsHost
   supportsShared <- platformSupportsSharedLibs
-  return (not win && supportsShared)
+  return (not windowsHost && supportsShared)
 
 -- | All 'Builder'-dependent command line arguments.
 defaultBuilderArgs :: Args
diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs
index 70bec0ecdcae57a7c9b7455a963c9a9a025be64f..4c5407186c34dc180e8966193f5e58f135ca53df 100644
--- a/hadrian/src/Settings/Packages.hs
+++ b/hadrian/src/Settings/Packages.hs
@@ -17,9 +17,11 @@ packageArgs = do
     intLib       <- getIntegerPackage
     compilerPath <- expr $ buildPath (vanillaContext stage compiler)
     gmpBuildPath <- expr gmpBuildPath
-    win          <- expr windowsHost
-    cross        <- expr (flag CrossCompiling)
     let includeGmp = "-I" ++ gmpBuildPath -/- "include"
+        -- Do not bind the result to a Boolean: this forces the configure rule
+        -- immediately and may lead to cyclic dependencies.
+        -- See: https://gitlab.haskell.org/ghc/ghc/issues/16809.
+        cross = flag CrossCompiling
 
     mconcat
         --------------------------------- base ---------------------------------
@@ -72,8 +74,8 @@ packageArgs = do
          , builder (Cabal Flags) ? mconcat
             [ ghcWithNativeCodeGen ? arg "ncg"
             , ghcWithInterpreter ? notStage0 ? arg "ghci"
-            , notStage0 ? (not win && not cross) ? arg "ext-interp"
-            , flag CrossCompiling ? arg "-terminfo"
+            , notStage0 ? not windowsHost ? notM cross ? arg "ext-interp"
+            , cross ? arg "-terminfo"
             , notStage0 ? intLib == integerGmp ?
               arg "integer-gmp"
             , notStage0 ? intLib == integerSimple ?
@@ -87,8 +89,8 @@ packageArgs = do
 
           , builder (Cabal Flags) ? mconcat
             [ ghcWithInterpreter ? notStage0 ? arg "ghci"
-            , notStage0 ? (not win && not cross) ? arg "ext-interp"
-            , flag CrossCompiling ? arg "-terminfo"
+            , notStage0 ? not windowsHost ? notM cross ? arg "ext-interp"
+            , cross ? arg "-terminfo"
             -- the 'threaded' flag is True by default, but
             -- let's record explicitly that we link all ghc
             -- executables with the threaded runtime.
@@ -96,7 +98,7 @@ packageArgs = do
 
         -------------------------------- ghcPkg --------------------------------
         , package ghcPkg ?
-          builder (Cabal Flags) ? flag CrossCompiling ? arg "-terminfo"
+          builder (Cabal Flags) ? cross ? arg "-terminfo"
 
         -------------------------------- ghcPrim -------------------------------
         , package ghcPrim ? mconcat
@@ -121,9 +123,9 @@ packageArgs = do
         -- behind the @-fghci@ flag.
         , package ghci ? mconcat
           [ notStage0 ? builder (Cabal Flags) ? arg "ghci"
-          , notStage0 ? builder (Cabal Flags) ? (not win && not cross)
+          , notStage0 ? builder (Cabal Flags) ? not windowsHost ? notM cross
                       ? arg "ext-interp"
-          , flag CrossCompiling ? stage0 ? builder (Cabal Flags) ? arg "ghci" ]
+          , cross ? stage0 ? builder (Cabal Flags) ? arg "ghci" ]
 
         -------------------------------- haddock -------------------------------
         , package haddock ?
@@ -131,7 +133,7 @@ packageArgs = do
 
         ------------------------------- haskeline ------------------------------
         , package haskeline ?
-          builder (Cabal Flags) ? flag CrossCompiling ? arg "-terminfo"
+          builder (Cabal Flags) ? cross ? arg "-terminfo"
 
         -------------------------------- hsc2hs --------------------------------
         , package hsc2hs ?
diff --git a/hadrian/src/Settings/Warnings.hs b/hadrian/src/Settings/Warnings.hs
index 42e7662cdc00829518c6a11a6f95aac7e2d9ccf0..ea89fea3ef01814d986549e507755d6382e900a5 100644
--- a/hadrian/src/Settings/Warnings.hs
+++ b/hadrian/src/Settings/Warnings.hs
@@ -2,7 +2,6 @@ module Settings.Warnings (defaultGhcWarningsArgs, ghcWarningsArgs) where
 
 import Expression
 import Oracles.Flag
-import Oracles.Setting
 import Packages
 import Settings
 
@@ -13,7 +12,7 @@ defaultGhcWarningsArgs :: Args
 defaultGhcWarningsArgs = mconcat
     [ notStage0 ? arg "-Wnoncanonical-monad-instances"
     , (not <$> flag GccIsClang) ? mconcat
-      [ (not <$> windowsHost ) ? arg "-optc-Werror=unused-but-set-variable"
+      [ not windowsHost ? arg "-optc-Werror=unused-but-set-variable"
       , arg "-optc-Wno-error=inline" ]
     , flag GccIsClang ? arg "-optc-Wno-unknown-pragmas" ]