[Git][ghc/ghc][wip/toolchain-selection] 2 commits: Revert "Mingw bundled toolchain"

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Tue Jul 4 16:34:44 UTC 2023



Rodrigo Mesquita pushed to branch wip/toolchain-selection at Glasgow Haskell Compiler / GHC


Commits:
b76647a2 by Rodrigo Mesquita at 2023-07-04T16:54:08+01:00
Revert "Mingw bundled toolchain"

This reverts commit 7d04d6bcb4a65d6dc97f1d59497c3c0a208b8be6.

Revert "Windows bundled toolchain, output path, etc"

This reverts commit 50089ea4b39885c38f1e6b02c9babebf47170d1c.

Revert "Add windows bundled toolchain specific flags"

This reverts commit a5734d7450890f739196d46610ba8d5558755782.

Adjust

- - - - -
d5c63707 by Rodrigo Mesquita at 2023-07-04T17:34:37+01:00
Fixes and extensions

- - - - -


7 changed files:

- hadrian/src/Oracles/Flag.hs
- m4/fp_link_supports_no_as_needed.m4
- m4/ghc_toolchain.m4
- utils/ghc-toolchain/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Monad.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Program.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs


Changes:

=====================================
hadrian/src/Oracles/Flag.hs
=====================================
@@ -79,8 +79,8 @@ platformSupportsGhciObjects = isJust <$> queryTargetTarget tgtMergeObjs
 
 arSupportsDashL :: Stage -> Action Bool
 -- ROMES:TODO: Build vs Host vs Target, is it Build and Host or Host and Target here?
-arSupportsDashL (Stage0 {}) = queryBuildTarget (Toolchain.arSupportsDashL . tgtAr)
-arSupportsDashL _           = queryHostTarget (Toolchain.arSupportsDashL . tgtAr)
+arSupportsDashL (Stage0 {}) = queryHostTarget (Toolchain.arSupportsDashL . tgtAr)
+arSupportsDashL _           = queryBuildTarget (Toolchain.arSupportsDashL . tgtAr)
 
 arSupportsAtFile :: Stage -> Action Bool
 arSupportsAtFile (Stage0 {}) = queryBuildTarget (Toolchain.arSupportsAtFile . tgtAr)


=====================================
m4/fp_link_supports_no_as_needed.m4
=====================================
@@ -5,7 +5,6 @@
 # See also Note [ELF needed shared libs]
 AC_DEFUN([FP_LINK_SUPPORTS_NO_AS_NEEDED],
 [
-    # Why isn't this working on i386?
     AC_MSG_CHECKING([whether Cc linker supports -Wl,--no-as-needed])
     echo 'int f(int a) {return 2*a;}' > conftest.a.c
     echo 'int f(int a); int main(int argc, char **argv) {return f(0);}' > conftest.b.c


=====================================
m4/ghc_toolchain.m4
=====================================
@@ -17,14 +17,18 @@ AC_DEFUN([ENABLE_GHC_TOOLCHAIN_ARG],
     fi
 ])
 
-dnl like ENABLE_GHC_TOOLCHAIN_ARG, but maps YES to --disable-X, and NO to --enable-X
-AC_DEFUN([ENABLE_GHC_TOOLCHAIN_ARG_NOT],
+AC_DEFUN([INVOKE_GHC_TOOLCHAIN],
 [
-    if test "$2" = "YES"; then
-        echo "--disable-$1" >> acargs
-    elif test "$2" = "NO"; then
-        echo "--enable-$1" >> acargs
-    fi
+    (
+        set --
+        while read -r arg; do
+            set -- "[$]@" "$arg"
+        done
+        # For now, we don't exit even if ghc-toolchain fails. We don't want to
+        # fail configure due to it, since the target file is still being generated by configure.
+        ./acghc-toolchain -v2 "[$]@" # || exit 1
+        python3 -c 'import sys; print(sys.argv)' "[$]@"
+    ) <acargs || exit 1
 ])
 
 AC_DEFUN([FIND_GHC_TOOLCHAIN],
@@ -35,67 +39,82 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
         -odir actmp-ghc-toolchain -hidir actmp-ghc-toolchain \
         utils/ghc-toolchain/Main.hs -o acghc-toolchain
 
+    # (1) Configure a toolchain for the build and host platform (we require that BUILD=HOST, so one toolchain suffices)
     rm -f acargs
+    echo "--triple=$HostPlatform" >> acargs
+    echo "--output=default.ghc-toolchain.host.target" >> acargs
+    dnl echo "--llvm-triple=$LlvmTarget" >> acargs
+    echo "--cc=$CC_STAGE0" >> acargs
+    dnl echo "--readelf=$READELF" >> acargs
+    dnl echo "--cpp=$CPPCmd" >> acargs
+    dnl echo "--hs-cpp=$HaskellCPPCmd" >> acargs
+    echo "--cc-link=$CC_STAGE0" >> acargs
+    dnl echo "--cxx=$CXX" >> acargs
+    echo "--ar=$AR_STAGE0" >> acargs
+    dnl echo "--ranlib=$RANLIB" >> acargs
+    dnl echo "--nm=$NM" >> acargs
 
-    # (1) Configure a toolchain for the build and host platform (we require that BUILD=HOST, so one toolchain suffices)
-    ./acghc-toolchain -v2 --triple="$HostPlatform" --output="default.host.ghc-toolchain.target"
-    # ROMES:TODO: Should we pass --bundled-windows-toolchain to the Host configuration?
+    echo "ACARGS-HOST"
+    cat acargs
+
+    INVOKE_GHC_TOOLCHAIN()
 
-    # (2) Configure a toolchain for the target platform 
-    # The resulting 
+    # (2) Configure a toolchain for the target platform (the toolchain is based
+    # on the triple (or manually specified), and runs on the platform
+    # configuring it and produces code for the given target)
+    # We might not find the correct toolchain, and fallback to the default
+    # toolchain. We should handle it more graciously.
+    #
+    # We pass the paths to the programs found by configure.
+    # The flags for the toolchain configured by ghc-toolchain will still be
+    # validated against those configured by configure, but ghc-toolchain
+    # doesn't take into account things like environment variables or bundled
+    # (windows) toolchains, so we explicitly pass them as arguments here.
+    # ghc-toolchain is still able to find programs if not explicitly given in
+    # the usual system locations, including the PATH, we are just explicit when
+    # calling it through configure.
+    rm -f acargs
     echo "--triple=$target" >> acargs
     echo "--output=default.ghc-toolchain.target" >> acargs
     echo "--llvm-triple=$LlvmTarget" >> acargs
-    # echo "--cc=$CC" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([cc-opt], [$CONF_CC_OPTS_STAGE1])
-
-    # # CPP flags
-    # echo "--cpp=$CPPCmd" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([cpp-opt], [$CONF_CPP_OPTS_STAGE1])
-
-    # # HS CPP flags
-    # echo "--hs-cpp=$HaskellCPPCmd" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$HaskellCPPArgs])
-
-    # echo "--cc-link=$CC" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$CONF_GCC_LINK_OPTS_STAGE1])
-    # echo "--cxx=$CXX" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([cxx-opt], [$CONF_CXX_OPTS_STAGE1])
-    # echo "--ar=$AR" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([ar-opt], [$ARFLAGS])
-    # echo "--ranlib=$RANLIB" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([ranlib-opt], [$RANLIBFLAGS])
-    # echo "--nm=$NM" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([nm-opt], [$NMFLAGS])
-    # echo "--readelf=$READELF" >> acargs
-    # ADD_GHC_TOOLCHAIN_ARG([readelf-opt], [$READELFFLAGS])
-
+    echo "--cc=$CC" >> acargs
+    echo "--readelf=$READELF" >> acargs
+    echo "--cpp=$CPPCmd" >> acargs
+    echo "--hs-cpp=$HaskellCPPCmd" >> acargs
+    echo "--cc-link=$CC" >> acargs
+    echo "--cxx=$CXX" >> acargs
+    echo "--ar=$AR" >> acargs
+    echo "--ranlib=$RANLIB" >> acargs
+    echo "--nm=$NM" >> acargs
     ENABLE_GHC_TOOLCHAIN_ARG([unregisterised], [$Unregisterised])
     ENABLE_GHC_TOOLCHAIN_ARG([tables-next-to-code], [$TablesNextToCode])
-    ENABLE_GHC_TOOLCHAIN_ARG_NOT([bundled-windows-toolchain], [$EnableDistroToolchain])
-    # romes:todo: when do we want to add bundled-windows-toolchain?
-    # For Host or Target?
-    if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO"; then
-        echo "--bundled-windows-toolchain=$mingwbin" >> acargs
-    else
-        true
-    fi
-
-    (
-        set --
-        while read -r arg; do
-            set -- "[$]@" "$arg"
-        done
-        # For now, we don't exit even if ghc-toolchain fails. We don't want to
-        # fail configure due to it, since the target file is still being generated by configure.
-        ./acghc-toolchain -v2 "[$]@" # || exit 1
-        python3 -c 'import sys; print(sys.argv)' "[$]@"
-    ) <acargs || exit 1
 
+    echo "ACARGS-TARGET"
     cat acargs
+
+    INVOKE_GHC_TOOLCHAIN()
+    
+    echo "ROMES:RESULT: default.target"
+    cat default.target
+    echo "ROMES:RESULT: default.ghc-toolchain.host.target"
+    cat default.ghc-toolchain.host.target
+    echo "ROMES:RESULT: default.ghc-toolchain.target"
     cat default.ghc-toolchain.target
 
     #rm -Rf acargs acghc-toolchain actmp-ghc-toolchain
+
+    dnl ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$HaskellCPPArgs])
+    dnl ADD_GHC_TOOLCHAIN_ARG([cpp-opt], [$CONF_CPP_OPTS_STAGE1])
+    dnl ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$CONF_GCC_LINK_OPTS_STAGE1])
+    dnl ADD_GHC_TOOLCHAIN_ARG([cxx-opt], [$CONF_CXX_OPTS_STAGE1])
+    dnl ADD_GHC_TOOLCHAIN_ARG([ar-opt], [$ARFLAGS])
+    dnl ADD_GHC_TOOLCHAIN_ARG([ranlib-opt], [$RANLIBFLAGS])
+    dnl ADD_GHC_TOOLCHAIN_ARG([nm-opt], [$NMFLAGS])
+    dnl ADD_GHC_TOOLCHAIN_ARG([readelf-opt], [$READELFFLAGS])
+    dnl ADD_GHC_TOOLCHAIN_ARG([cc-opt], [$CONF_CC_OPTS_STAGE1])
+
+    dnl Note: if we weren't passing the paths to the programs explicitly, to make
+    dnl ghc-toolchain use the bundled windows toolchain, simply add it to the search PATH
 ])
 
 
@@ -115,4 +134,7 @@ AC_DEFUN([VALIDATE_GHC_TOOLCHAIN],[
                 https://www.haskell.org/ghc/reportabug
       ])
     fi
+
+    echo "default.target printed:"
+    cat default.target
 ])


=====================================
utils/ghc-toolchain/Main.hs
=====================================
@@ -6,7 +6,6 @@ module Main where
 import Control.Monad
 import Data.Char (toUpper)
 import Data.Maybe (isNothing,fromMaybe)
-import Data.List (isInfixOf)
 import System.Exit
 import System.Console.GetOpt
 import System.Environment
@@ -48,8 +47,6 @@ data Opts = Opts
     , optMergeObjs :: ProgOpt
     , optWindres   :: ProgOpt
     , optDllwrap   :: ProgOpt
-    , optBundledWindowsToolchain :: Maybe String
-    , optUseBundledWindowsToolchain :: Maybe Bool
     , optUnregisterised :: Maybe Bool
     , optTablesNextToCode :: Maybe Bool
     , optUseLibFFIForAdjustors :: Maybe Bool
@@ -76,8 +73,6 @@ emptyOpts = Opts
     , optMergeObjs = po0
     , optDllwrap   = po0
     , optWindres   = po0
-    , optUseBundledWindowsToolchain = Nothing
-    , optBundledWindowsToolchain = Nothing
     , optUnregisterised = Nothing
     , optTablesNextToCode = Nothing
     , optUseLibFFIForAdjustors = Nothing
@@ -110,12 +105,6 @@ _optTriple = Lens optTriple (\x o -> o {optTriple=x})
 _optLlvmTriple :: Lens Opts (Maybe String)
 _optLlvmTriple = Lens optLlvmTriple (\x o -> o {optLlvmTriple=x})
 
-_optBundledWindowsToolchain :: Lens Opts (Maybe String)
-_optBundledWindowsToolchain = Lens optBundledWindowsToolchain (\x o -> o {optBundledWindowsToolchain=x})
-
-_optUseBundledWindowsToolchain :: Lens Opts (Maybe Bool)
-_optUseBundledWindowsToolchain = Lens optUseBundledWindowsToolchain (\x o -> o {optUseBundledWindowsToolchain=x})
-
 _optOutput :: Lens Opts String
 _optOutput = Lens optOutput (\x o -> o {optOutput=x})
 
@@ -148,11 +137,9 @@ options =
     , verbosityOpt
     , keepTempOpt
     , outputOpt
-    , bundledWindowsToolchainOpt
     ] ++
     concat
-    [ enableDisable "bundled-windows-toolchain" "Do not use bundled Windows toolchain binaries" _optUseBundledWindowsToolchain
-    , enableDisable "unregisterised" "unregisterised backend" _optUnregisterised
+    [ enableDisable "unregisterised" "unregisterised backend" _optUnregisterised
     , enableDisable "tables-next-to-code" "Tables-next-to-code optimisation" _optTablesNextToCode
     , enableDisable "libffi-adjustors" "Force use of libffi for adjustors, even on platforms which have support for more efficient, native adjustors." _optUseLibFFIForAdjustors
     , enableDisable "ld-override" "override gcc's default linker" _optLdOvveride
@@ -220,9 +207,6 @@ options =
     outputOpt = Option ['o'] ["output"] (ReqArg (set _optOutput) "OUTPUT")
         "The output path for the generated target toolchain configuration"
 
-    bundledWindowsToolchainOpt = Option [] ["bundled-windows-toolchain"] (OptArg (set _optBundledWindowsToolchain) "path to bundled windows toolchain")
-        "The path to the bundled Windows toolchain binaries."
-
 main :: IO ()
 main = do
     argv <- getArgs
@@ -230,32 +214,11 @@ main = do
     let opts = foldr (.) id opts0 emptyOpts
     case errs of
       [] -> do
-          -- Note that we inline the infix check for `mingw32` since `parseTriple` is harder to call
-          let isWindows = "mingw32" `isInfixOf` optTriple opts
-
-          -- Validate that, on a windows platform, either --disable-bundled-windows-toolchain
-          -- or --bundled-windows-toolchain=path was specified
-          case ( isWindows
-               , optUseBundledWindowsToolchain opts
-               , optBundledWindowsToolchain opts) of
-            (False, _, Just _)    ->
-              putStrLn "Warning: Ignoring --bundled-windows-toolchain since --triple is a non-windows platform"
-            (False, _, _)         -> pure ()
-            (True, Just False, Just _) ->
-              putStrLn "Warning: Ignoring --disabled-bundled-windows-toolchain since --bundled-windows-toolchain was specified"
-            (True, Just False, _) -> pure ()
-            (True, _, Nothing)    -> do
-              putStrLn "On windows, either a path to the bundled toolchain must be given with --bundled-windows-toolchain=\"...\", or --disable-bundled-windows-toolchain must be specified to use another mingw distribution."
-              exitWith (ExitFailure 1)
-
           let env = Env { verbosity = optVerbosity opts
                         , targetPrefix = case optTargetPrefix opts of
                                            Just prefix -> Just prefix
                                            Nothing -> Just $ optTriple opts ++ "-"
                         , keepTemp = optKeepTemp opts
-                        , bundledWindowsToolchain = if isWindows
-                                                       then optBundledWindowsToolchain opts
-                                                       else Nothing
                         , logContexts = []
                         }
           r <- runM env (run opts)


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Monad.hs
=====================================
@@ -6,7 +6,6 @@ module GHC.Toolchain.Monad
     , M
     , runM
     , getEnv
-    , asksEnv
     , makeM
     , throwE
     , ifCrossCompiling
@@ -39,7 +38,6 @@ import System.IO hiding (readFile, writeFile, appendFile)
 
 data Env = Env { verbosity    :: Int
                , targetPrefix :: Maybe String
-               , bundledWindowsToolchain :: Maybe String -- ^ Whether to use the bundled windows toolchain. This is only `Just` on windows and when --bundled-windows-toolchain was specified.
                , keepTemp     :: Bool
                , logContexts  :: [String]
                }
@@ -54,9 +52,6 @@ runM env (M k) =
 getEnv :: M Env
 getEnv = M $ lift Reader.ask
 
-asksEnv :: (Env -> a) -> M a
-asksEnv f = M $ lift (Reader.asks f)
-
 makeM :: IO (Either [Error] a) -> M a
 makeM io = M (Except.ExceptT (Reader.ReaderT (\env -> io)))
 


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Program.hs
=====================================
@@ -1,4 +1,3 @@
-{-# LANGUAGE LambdaCase #-}
 module GHC.Toolchain.Program
     ( Program(..)
     , _prgPath
@@ -130,17 +129,10 @@ findProgram description userSpec candidates
       toProgram path = Program { prgPath = path, prgFlags = fromMaybe [] (poFlags userSpec) }
 
       find_it name = do
-        r <- asksEnv bundledWindowsToolchain >>= \case
-
-          -- Find executable in the bundled windows toolchain
-          Just path -> listToMaybe <$> liftIO (findExecutablesInDirectories [path] name)
-
-          -- Find executable in system (see 'findExecutable' from System.Directory)
-          Nothing -> liftIO (findExecutable name)
-
-        case r of
-          Nothing -> throwE $ name ++ " not found in search path"
-          Just x -> return x
+          r <- liftIO $ findExecutable name
+          case r of
+            Nothing -> throwE $ name ++ " not found in search path"
+            Just x -> return x
 
 -------------------- Compiling utilities --------------------
 


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
=====================================
@@ -40,13 +40,14 @@ findCc llvmTarget progOpt = checking "for C compiler" $ do
     -- there's a more optimal one
     ccProgram' <- findProgram "C compiler" progOpt ["gcc", "clang", "cc"]
 
-    ccProgram <- asksEnv bundledWindowsToolchain >>= \case
-      Nothing -> pure ccProgram'
-      Just _  ->
-        -- Signal that we are linking against UCRT with the _UCRT macro. This is
-        -- necessary to ensure correct behavior when MinGW-w64 headers are in the
-        -- header include path (#22159).
-        pure $ ccProgram' & _prgFlags %++ "--rtlib=compiler-rt -D_UCRT"
+                    -- we inline the windows check here because we need Cc to call parseTriple
+    let ccProgram = if "mingw32" `isInfixOf` llvmTarget && takeBaseName (prgPath ccProgram') == "clang"
+         then ccProgram'
+         else
+           -- Signal that we are linking against UCRT with the _UCRT macro. This is
+           -- necessary on windows clang to ensure correct behavior when
+           -- MinGW-w64 headers are in the header include path (#22159).
+           ccProgram' & _prgFlags %++ "--rtlib=compiler-rt -D_UCRT"
 
     cc' <- ignoreUnusedArgs $ Cc {ccProgram}
     cc  <- ccSupportsTarget llvmTarget cc'



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78fef9efaf78b03ad5257f84803e578c87afd023...d5c63707b2db9805e263604f0fd7b1e20d1407e0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78fef9efaf78b03ad5257f84803e578c87afd023...d5c63707b2db9805e263604f0fd7b1e20d1407e0
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/20230704/e881d9a9/attachment-0001.html>


More information about the ghc-commits mailing list