[Git][ghc/ghc][wip/toolchain-selection] Try to add locally-executable arg

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Mon Jul 10 11:06:36 UTC 2023



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


Commits:
9e6ffc7f by Rodrigo Mesquita at 2023-07-10T12:06:20+01:00
Try to add locally-executable arg

- - - - -


7 changed files:

- default.target.in
- hadrian/src/Context.hs
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- utils/ghc-toolchain/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Monad.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs


Changes:

=====================================
default.target.in
=====================================
@@ -1,6 +1,7 @@
 Target
 { tgtArchOs = ArchOS {archOS_arch = @HaskellTargetArch@, archOS_OS = @HaskellTargetOs@}
 , tgtVendor = @TargetVendor_CPPMaybeStr@
+, tgtLocallyExecutable = @NotCrossCompilingBool@
 , tgtSupportsGnuNonexecStack = @TargetHasGnuNonexecStackBool@
 , tgtSupportsSubsectionsViaSymbols = @TargetHasSubsectionsViaSymbolsBool@
 , tgtSupportsIdentDirective = @TargetHasIdentDirectiveBool@
@@ -11,9 +12,9 @@ Target
 , tgtUnregisterised = @UnregisterisedBool@
 , tgtTablesNextToCode = @TablesNextToCodeBool@
 , tgtUseLibffiForAdjustors = @UseLibffiForAdjustorsBool@
-, tgtCCompiler = Cc {ccProgram = Program {prgPath = "@SettingsCCompilerCommand@", prgFlags = @CFLAGSList@}}
-, tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@SettingsCxxCompilerCommand@", prgFlags = @CXXFLAGSList@}}
-, tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@SettingsCPPCommand@", prgFlags = @CPPFLAGSList@}}
+, tgtCCompiler = Cc {ccProgram = Program {prgPath = "@SettingsCCompilerCommand@", prgFlags = @SettingsCCompilerFlagsList@}}
+, tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@SettingsCxxCompilerCommand@", prgFlags = @SettingsCxxCompilerFlagsList@}}
+, tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@SettingsCPPCommand@", prgFlags = @SettingsCPPFlagsList@}}
 , tgtHsCPreprocessor = HsCpp {hsCppProgram = Program {prgPath = "@SettingsHaskellCPPCommand@", prgFlags = @SettingsHaskellCPPFlagsList@}}
 , tgtCCompilerLink = CcLink
 { ccLinkProgram = Program {prgPath = "@SettingsCCompilerCommand@", prgFlags = @SettingsCCompilerLinkFlagsList@}


=====================================
hadrian/src/Context.hs
=====================================
@@ -20,7 +20,6 @@ import Hadrian.Expression
 import Hadrian.Haskell.Cabal
 import Oracles.Setting
 import GHC.Toolchain.Target (Target(..))
-import Hadrian.Oracles.TextFile
 import GHC.Platform.ArchOS
 
 -- | Most targets are built only one way, hence the notion of 'vanillaContext'.


=====================================
m4/ghc_toolchain.m4
=====================================
@@ -17,6 +17,15 @@ AC_DEFUN([ENABLE_GHC_TOOLCHAIN_ARG],
     fi
 ])
 
+AC_DEFUN([ENABLE_GHC_TOOLCHAIN_NOT_ARG],
+[
+    if test "$2" = "NO"; then
+        echo "--enable-$1" >> acargs
+    elif test "$2" = "YES"; then
+        echo "--disable-$1" >> acargs
+    fi
+])
+
 AC_DEFUN([INVOKE_GHC_TOOLCHAIN],
 [
     (
@@ -89,6 +98,7 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
     echo "--readelf=$READELF" >> acargs
     echo "--windres=$WindresCmd" >> acargs
     echo "--dllwrap=$DllWrapCmd" >> acargs
+    ENABLE_GHC_TOOLCHAIN_NOT_ARG([locally-executable], [$CrossCompiling])
     ENABLE_GHC_TOOLCHAIN_ARG([unregisterised], [$Unregisterised])
     ENABLE_GHC_TOOLCHAIN_ARG([tables-next-to-code], [$TablesNextToCode])
 


=====================================
m4/prep_target_file.m4
=====================================
@@ -52,6 +52,26 @@ AC_DEFUN([PREP_BOOLEAN],[
     AC_SUBST([$1Bool])
 ])
 
+# PREP_NOT_BOOLEAN
+# ============
+#
+# Issue a substitution with True/False of [Not$1Bool] when $1 has NO/YES value
+# $1 = boolean variable to substitute
+AC_DEFUN([PREP_NOT_BOOLEAN],[
+    case "$$1" in
+        NO)
+          Not$1Bool=True
+          ;;
+        YES)
+          Not$1Bool=False
+          ;;
+        *)
+          AC_MSG_ERROR([m4/prep_target_file.m4: Expecting YES/NO but got $$1 in $1])
+          ;;
+    esac
+    AC_SUBST([Not$1Bool])
+])
+
 # PREP_LIST
 # ============
 #
@@ -103,6 +123,7 @@ AC_DEFUN([PREP_TARGET_FILE],[
     PREP_BOOLEAN([UseLibffiForAdjustors])
     PREP_BOOLEAN([ArIsGNUAr])
     PREP_BOOLEAN([ArNeedsRanLib])
+    PREP_NOT_BOOLEAN([CrossCompiling])
     PREP_LIST([SettingsMergeObjectsFlags])
     PREP_LIST([ArArgs])
     PREP_LIST([SettingsCCompilerLinkFlags])


=====================================
utils/ghc-toolchain/Main.hs
=====================================
@@ -33,6 +33,7 @@ import GHC.Toolchain.Tools.Readelf
 data Opts = Opts
     { optTriple    :: String
     , optTargetPrefix :: Maybe String
+    , optLocallyExecutable :: Maybe Bool
     , optLlvmTriple :: Maybe String
     , optOutput    :: String
     , optCc        :: ProgOpt
@@ -59,6 +60,7 @@ emptyOpts :: Opts
 emptyOpts = Opts
     { optTriple    = ""
     , optTargetPrefix = Nothing
+    , optLocallyExecutable = Nothing
     , optLlvmTriple = Nothing
     , optOutput    = ""
     , optCc        = po0
@@ -111,16 +113,11 @@ _optOutput = Lens optOutput (\x o -> o {optOutput=x})
 _optTargetPrefix :: Lens Opts (Maybe String)
 _optTargetPrefix = Lens optTargetPrefix (\x o -> o {optTargetPrefix=x})
 
-_optUnregisterised :: Lens Opts (Maybe Bool)
+_optLocallyExecutable, _optUnregisterised, _optTablesNextToCode, _optUseLibFFIForAdjustors, _optLdOvveride :: Lens Opts (Maybe Bool)
+_optLocallyExecutable = Lens optLocallyExecutable (\x o -> o {optLocallyExecutable=x})
 _optUnregisterised = Lens optUnregisterised (\x o -> o {optUnregisterised=x})
-
-_optTablesNextToCode :: Lens Opts (Maybe Bool)
 _optTablesNextToCode = Lens optTablesNextToCode (\x o -> o {optTablesNextToCode=x})
-
-_optUseLibFFIForAdjustors :: Lens Opts (Maybe Bool)
 _optUseLibFFIForAdjustors = Lens optUseLibFFIForAdjustors (\x o -> o {optUseLibFFIForAdjustors=x})
-
-_optLdOvveride :: Lens Opts (Maybe Bool)
 _optLdOvveride = Lens optLdOverride (\x o -> o {optLdOverride=x})
 
 _optVerbosity :: Lens Opts Int
@@ -143,6 +140,7 @@ options =
     , 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
+    , enableDisable "locally-executable" "A target prefix which will be added to all tool names when searching for toolchain components" _optLocallyExecutable
     ] ++
     concat
     [ progOpts "cc" "C compiler" _optCc
@@ -191,6 +189,7 @@ options =
     targetPrefixOpt = Option ['T'] ["target-prefix"] (ReqArg (set _optTargetPrefix . Just) "PREFIX")
         "A target prefix which will be added to all tool names when searching for toolchain components"
 
+
     verbosityOpt = Option ['v'] ["verbose"] (OptArg f "N") "set output verbosity"
       where
         f mb = set _optVerbosity (parseVerbosity mb)
@@ -219,6 +218,7 @@ main = do
                                            Just prefix -> Just prefix
                                            Nothing -> Just $ optTriple opts ++ "-"
                         , keepTemp = optKeepTemp opts
+                        , canLocallyExecute = fromMaybe True (optLocallyExecutable opts)
                         , logContexts = []
                         }
           r <- runM env (run opts)
@@ -372,6 +372,7 @@ mkTarget opts = do
 
     let t = Target { tgtArchOs = archOs
                    , tgtVendor
+                   , tgtLocallyExecutable = fromMaybe True (optLocallyExecutable opts)
                    , tgtCCompiler = cc
                    , tgtCxxCompiler = cxx
                    , tgtCPreprocessor = cpp


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Monad.hs
=====================================
@@ -39,6 +39,7 @@ import System.IO hiding (readFile, writeFile, appendFile)
 data Env = Env { verbosity    :: Int
                , targetPrefix :: Maybe String
                , keepTemp     :: Bool
+               , canLocallyExecute :: Bool
                , logContexts  :: [String]
                }
 
@@ -122,4 +123,7 @@ ifCrossCompiling
     :: M a  -- ^ what to do when cross-compiling
     -> M a  -- ^ what to do otherwise
     -> M a
-ifCrossCompiling cross other = other -- TODO
+ifCrossCompiling cross other = do
+  canExec <- canLocallyExecute <$> getEnv
+  if not canExec then cross -- can't execute, this is a cross target
+                 else other -- can execute, run the other action


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
=====================================
@@ -42,7 +42,7 @@ data Target = Target
     { -- Platform
       tgtArchOs :: ArchOS
     , tgtVendor :: Maybe String
-    -- , tgtHostCanExecute :: Bool -- TODO: Rename hostCanExecute? We might need this to determine whether or not we can execute a program when configuring it
+    , tgtLocallyExecutable :: Bool
     , tgtSupportsGnuNonexecStack :: Bool
     , tgtSupportsSubsectionsViaSymbols :: Bool
     , tgtSupportsIdentDirective :: Bool
@@ -79,6 +79,7 @@ instance Show Target where
     [ "Target"
     , "{ tgtArchOs = " ++ show tgtArchOs
     , ", tgtVendor = " ++ show tgtVendor
+    , ", tgtLocallyExecutable = " ++ show tgtLocallyExecutable
     , ", tgtSupportsGnuNonexecStack = " ++ show tgtSupportsGnuNonexecStack
     , ", tgtSupportsSubsectionsViaSymbols = " ++ show tgtSupportsSubsectionsViaSymbols
     , ", tgtSupportsIdentDirective = " ++ show tgtSupportsIdentDirective



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e6ffc7fb6460ecedc7b4378cca2116ae160a03f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e6ffc7fb6460ecedc7b4378cca2116ae160a03f
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/20230710/d04cbcd3/attachment-0001.html>


More information about the ghc-commits mailing list