[Git][ghc/ghc][wip/toolchain-selection] 2 commits: configure: Create and validate toolchain target file
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Mon Jun 5 22:17:52 UTC 2023
Rodrigo Mesquita pushed to branch wip/toolchain-selection at Glasgow Haskell Compiler / GHC
Commits:
0d39eb62 by Rodrigo Mesquita at 2023-06-05T23:13:31+01:00
configure: Create and validate toolchain target file
- - - - -
2bd70e58 by Rodrigo Mesquita at 2023-06-05T23:13:35+01:00
Fixes to match configure output
- - - - -
10 changed files:
- configure.ac
- + default.target.in
- distrib/configure.ac.in
- m4/ghc_toolchain.m4
- + m4/prep_target_file.m4
- utils/ghc-toolchain/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Ar.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
Changes:
=====================================
configure.ac
=====================================
@@ -644,7 +644,6 @@ dnl CONF_CC_OPTS_STAGE[012] accordingly.
FP_CC_SUPPORTS_TARGET([$CC_STAGE0], [CONF_CC_OPTS_STAGE0], [CONF_CXX_OPTS_STAGE0], [CONF_GCC_LINKER_OPTS_STAGE0])
FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1], [CONF_GCC_LINKER_OPTS_STAGE1])
FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_CXX_OPTS_STAGE2], [CONF_GCC_LINKER_OPTS_STAGE2])
-FIND_GHC_TOOLCHAIN
# CPP, CPPFLAGS
# --with-cpp/-with-cpp-flags
@@ -1168,6 +1167,11 @@ checkMake380() {
checkMake380 make
checkMake380 gmake
+# Toolchain target files
+PREP_TARGET_FILE
+FIND_GHC_TOOLCHAIN
+VALIDATE_GHC_TOOLCHAIN
+
AC_CONFIG_FILES(
[ mk/project.mk
hadrian/cfg/system.config
@@ -1176,6 +1180,7 @@ AC_CONFIG_FILES(
hadrian/ghci-stack
docs/users_guide/ghc_config.py
distrib/configure.ac
+ default.target
])
dnl Create the VERSION file, satisfying #22322.
=====================================
default.target.in
=====================================
@@ -0,0 +1,39 @@
+Target
+{ tgtArchOs = ArchOS {archOS_arch = @HaskellHostArch@, archOS_OS = @HaskellHostOs@}
+, tgtSupportsGnuNonexecStack = @TargetHasGnuNonexecStackBool@
+, tgtSupportsSubsectionsViaSymbols = @TargetHasSubsectionsViaSymbolsBool@
+, tgtSupportsIdentDirective = @TargetHasIdentDirectiveBool@
+, tgtWordSize = WS at TargetWordSize@
+, tgtEndianness = LittleEndian
+, tgtSymbolsHaveLeadingUnderscore = @LeadingUnderscoreBool@
+, tgtLlvmTarget = "@HostPlatform@"
+, tgtUnregisterised = @UnregisterisedBool@
+, tgtTablesNextToCode = @TablesNextToCodeBool@
+, tgtUseLibffiForAdjustors = @UseLibffiForAdjustorsBool@
+, tgtCCompiler = Cc {ccProgram = Program {prgPath = "@SettingsCCompilerCommand@", prgFlags = @SettingsCCompilerFlagsList@}}
+, tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@SettingsCxxCompilerCommand@", prgFlags = @SettingsCxxCompilerFlagsList@}}
+, tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@CPPCmd@", prgFlags = @CONF_CPP_OPTS_STAGE1List@}}
+, tgtHsCPreprocessor = HsCpp {hsCppProgram = Program {prgPath = "@HaskellCPPCmd@", prgFlags = @HaskellCPPArgsList@}}
+, tgtCCompilerLink = CcLink
+{ ccLinkProgram = Program {prgPath = "@SettingsCCompilerCommand@", prgFlags = @SettingsCCompilerLinkFlagsList@}
+, ccLinkSupportsNoPie = @SettingsCCompilerSupportsNoPieBool@
+, ccLinkSupportsCompactUnwind = @LdHasNoCompactUnwindBool@
+, ccLinkSupportsFilelist = @LdHasFilelistBool@
+, ccLinkSupportsResponseFiles = @LdSupportsResponseFilesBool@
+, ccLinkIsGnu = @LdIsGNULdBool@
+}
+
+, tgtAr = Ar
+{ arMkArchive = Program {prgPath = "@AR@", prgFlags = @ArArgsList@}
+, arIsGnu = False
+, arSupportsAtFile = @ArSupportsAtFileBool@
+, arSupportsDashL = @ArSupportsDashLBool@
+, arNeedsRanlib = False
+}
+
+, tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@REAL_RANLIB_CMD@", prgFlags = []}})
+, tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}}
+, tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@SettingsMergeObjectsCommand@", prgFlags = @SettingsMergeObjectsFlagsList@}})
+, tgtDllwrap = Nothing
+, tgtWindres = Nothing
+}
=====================================
distrib/configure.ac.in
=====================================
@@ -303,6 +303,11 @@ checkMake380() {
checkMake380 make
checkMake380 gmake
+# Toolchain target files
+PREP_TARGET_FILE
+FIND_GHC_TOOLCHAIN
+VALIDATE_GHC_TOOLCHAIN
+
echo "****************************************************"
echo "Configuration done, ready to 'make install'"
echo "(see README and INSTALL files for more info.)"
=====================================
m4/ghc_toolchain.m4
=====================================
@@ -66,8 +66,19 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
) <acargs || exit 1
cat acargs
- cat default.target
+ cat default.ghc-toolchain.target
#rm -Rf acargs acghc-toolchain actmp-ghc-toolchain
])
+
+AC_DEFUN([VALIDATE_GHC_TOOLCHAIN],[
+ A="default.target"
+ B="default.ghc-toolchain.target"
+ diff_output=`diff "$A" "$B" 2>&1`
+ if test -z "$diff_output"; then
+ true
+ else
+ AC_MSG_WARN([Differences found between $A and $B: $diff_output])
+ fi
+])
=====================================
m4/prep_target_file.m4
=====================================
@@ -0,0 +1,71 @@
+# PREP_BOOLEAN
+# ============
+#
+# Issue a substitution with True/False of [$1Bool] when $1 has YES/NO value
+# $1 = boolean variable to substitute
+AC_DEFUN([PREP_BOOLEAN],[
+ case "$$1" in
+ YES)
+ $1Bool=True
+ ;;
+ NO)
+ $1Bool=False
+ ;;
+ *)
+ AC_MSG_ERROR([Expecting YES/NO but got $$1 in $1])
+ ;;
+ esac
+ AC_SUBST([$1Bool])
+])
+
+# PREP_LIST
+# ============
+#
+# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a
+# space-separated list of args
+# $1 = list variable to substitute
+dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'.
+AC_DEFUN([PREP_LIST],[
+ TMP_ARR=($$1)
+ $1List="@<:@"
+ if test -z "$TMP_ARR"; then
+ true
+ else
+ $1List="${$1List}\"${TMP_ARR@<:@0@:>@}\""
+ for arg in "${TMP_ARR@<:@@@:>@:1}"
+ do
+ $1List="${$1List},\"$arg\""
+ done
+ fi
+ $1List="${$1List}@:>@"
+ AC_SUBST([$1List])
+ unset TMP_ARR
+])
+
+# Eventually: PREP_BUILD_TARGET_FILE, PREP_HOST_TARGET_FILE, PREP_TARGET_TARGET_FILE
+# Prepares required substitutions to generate the target file
+AC_DEFUN([PREP_TARGET_FILE],[
+ PREP_BOOLEAN([LdSupportsResponseFiles])
+ PREP_BOOLEAN([TargetHasGnuNonexecStack])
+ PREP_BOOLEAN([LeadingUnderscore])
+ PREP_BOOLEAN([ArSupportsAtFile])
+ PREP_BOOLEAN([ArSupportsDashL])
+ PREP_BOOLEAN([TargetHasIdentDirective])
+ PREP_BOOLEAN([SettingsCCompilerSupportsNoPie])
+ PREP_BOOLEAN([LdHasFilelist])
+ PREP_BOOLEAN([LdIsGNULd])
+ PREP_BOOLEAN([LdHasNoCompactUnwind])
+ PREP_BOOLEAN([TargetHasSubsectionsViaSymbols])
+ PREP_BOOLEAN([Unregisterised])
+ PREP_BOOLEAN([TablesNextToCode])
+ PREP_BOOLEAN([UseLibffiForAdjustors])
+ PREP_LIST([SettingsMergeObjectsFlags])
+ PREP_LIST([ArArgs])
+ PREP_LIST([SettingsCCompilerLinkFlags])
+ PREP_LIST([HaskellCPPArgs])
+ PREP_LIST([CONF_CPP_OPTS_STAGE1])
+ PREP_LIST([SettingsCxxCompilerFlags])
+ PREP_LIST([SettingsCCompilerFlags])
+])
+
+AC_DEFUN()
=====================================
utils/ghc-toolchain/Main.hs
=====================================
@@ -160,9 +160,11 @@ options =
-- Empty list of flags is as if it was unspecified
updatePoFlags "" existingOpts = existingOpts
- -- Otherwise append specified flags to existing flags or make new
+ -- Otherwise prepend specified flags to existing flags or make new
updatePoFlags newOpts Nothing = Just [newOpts]
- updatePoFlags newOpts (Just eopts) = Just (eopts ++ [newOpts])
+ updatePoFlags newOpts (Just eopts) = Just (newOpts:eopts)
+ -- NB: By prepending, the resulting flags will match the left-to-right
+ -- order they were passed in
enableDisable :: String -> String -> Lens Opts (Maybe Bool) -> [OptDescr (Opts -> Opts)]
@@ -216,7 +218,9 @@ run :: Opts -> M ()
run opts = do
tgt <- mkTarget opts
logDebug $ "Final Target: " ++ show tgt
- writeFile "default.target" (show tgt)
+ let file = "default.ghc-toolchain.target"
+ writeFile file (show tgt)
+ appendFile file "\n" -- eol
optional :: M a -> M (Maybe a)
optional k = fmap Just k <|> pure Nothing
@@ -327,7 +331,7 @@ mkTarget opts = do
tgtWordSize <- checkWordSize cc
tgtEndianness <- checkEndianness cc
tgtSymbolsHaveLeadingUnderscore <- checkLeadingUnderscore cc nm
- tgtSupportsSubsectionsViaSymbols <- checkSubsectionsViaSymbols cc
+ tgtSupportsSubsectionsViaSymbols <- checkSubsectionsViaSymbols archOs cc
tgtSupportsIdentDirective <- checkIdentDirective cc
tgtSupportsGnuNonexecStack <- checkGnuNonexecStack archOs cc
@@ -338,7 +342,7 @@ mkTarget opts = do
tgtUseLibffi <- determineUseLibFFIForAdjustors archOs (optUseLibFFIForAdjustors opts)
when tgtUnregisterised $ do
-- The via-C code generator requires these
- let prog = "int main(int argc, char** argv) { return 0; }I"
+ let prog = "int main(int argc, char** argv) { return 0; }"
via_c_args = ["-fwrapv", "-fno-builtin"]
forM_ via_c_args $ \arg -> checking ("support of "++arg) $ withTempDir $ \dir -> do
let cc' = over (_ccProgram % _prgFlags) (++ [arg]) cc
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
=====================================
@@ -102,11 +102,17 @@ checkLeadingUnderscore cc nm = checking ctxt $ withTempDir $ \dir -> do
prog = "int func(void) { return 0; }"
ctxt = "whether symbols have leading underscores"
-checkSubsectionsViaSymbols :: Cc -> M Bool
-checkSubsectionsViaSymbols =
- testCompile
- "whether .subsections-via-symbols directive is supported"
- (asmStmt ".subsections_via_symbols")
+checkSubsectionsViaSymbols :: ArchOS -> Cc -> M Bool
+checkSubsectionsViaSymbols archos cc =
+ case archOS_arch archos of
+ ArchAArch64 ->
+ -- subsections via symbols is busted on arm64
+ -- TODO: ^ is this comment up to date?
+ return False
+ _ ->
+ testCompile
+ "whether .subsections-via-symbols directive is supported"
+ (asmStmt ".subsections_via_symbols") cc
checkIdentDirective :: Cc -> M Bool
checkIdentDirective =
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE RecordWildCards #-}
module GHC.Toolchain.Target where
import GHC.Platform.ArchOS
@@ -60,7 +61,35 @@ data Target = Target
, tgtDllwrap :: Maybe Program
, tgtWindres :: Maybe Program
}
- deriving (Show, Read, Eq, Ord)
+ deriving (Read, Eq, Ord)
+
+instance Show Target where
+ show Target{..} = unlines
+ [ "Target"
+ , "{ tgtArchOs = " ++ show tgtArchOs
+ , ", tgtSupportsGnuNonexecStack = " ++ show tgtSupportsGnuNonexecStack
+ , ", tgtSupportsSubsectionsViaSymbols = " ++ show tgtSupportsSubsectionsViaSymbols
+ , ", tgtSupportsIdentDirective = " ++ show tgtSupportsIdentDirective
+ , ", tgtWordSize = " ++ show tgtWordSize
+ , ", tgtEndianness = " ++ show tgtEndianness
+ , ", tgtSymbolsHaveLeadingUnderscore = " ++ show tgtSymbolsHaveLeadingUnderscore
+ , ", tgtLlvmTarget = " ++ show tgtLlvmTarget
+ , ", tgtUnregisterised = " ++ show tgtUnregisterised
+ , ", tgtTablesNextToCode = " ++ show tgtTablesNextToCode
+ , ", tgtUseLibffiForAdjustors = " ++ show tgtUseLibffiForAdjustors
+ , ", tgtCCompiler = " ++ show tgtCCompiler
+ , ", tgtCxxCompiler = " ++ show tgtCxxCompiler
+ , ", tgtCPreprocessor = " ++ show tgtCPreprocessor
+ , ", tgtHsCPreprocessor = " ++ show tgtHsCPreprocessor
+ , ", tgtCCompilerLink = " ++ show tgtCCompilerLink
+ , ", tgtAr = " ++ show tgtAr
+ , ", tgtRanlib = " ++ show tgtRanlib
+ , ", tgtNm = " ++ show tgtNm
+ , ", tgtMergeObjs = " ++ show tgtMergeObjs
+ , ", tgtDllwrap = " ++ show tgtDllwrap
+ , ", tgtWindres = " ++ show tgtDllwrap
+ , "}"
+ ]
-- | The word size as an integer representing the number of bytes
wordSize2Bytes :: WordSize -> Int
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Ar.hs
=====================================
@@ -17,7 +17,19 @@ data Ar = Ar { arMkArchive :: Program
, arSupportsDashL :: Bool
, arNeedsRanlib :: Bool
}
- deriving (Show, Read, Eq, Ord)
+ deriving (Read, Eq, Ord)
+
+-- These instances are more suitable for diffing
+instance Show Ar where
+ show Ar{..} = unlines
+ [ "Ar"
+ , "{ arMkArchive = " ++ show arMkArchive
+ , ", arIsGnu = " ++ show arIsGnu
+ , ", arSupportsAtFile = " ++ show arSupportsAtFile
+ , ", arSupportsDashL = " ++ show arSupportsDashL
+ , ", arNeedsRanlib = " ++ show arNeedsRanlib
+ , "}"
+ ]
findAr :: ProgOpt -> M Ar
findAr progOpt = checking "for 'ar'" $ do
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
=====================================
@@ -1,5 +1,6 @@
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
module GHC.Toolchain.Tools.Link ( CcLink(..), findCcLink ) where
@@ -24,7 +25,20 @@ data CcLink = CcLink { ccLinkProgram :: Program
, ccLinkSupportsResponseFiles :: Bool
, ccLinkIsGnu :: Bool -- We once thought this could instead be LdSupportsGcSections, but then realized it couldn't IIRC
}
- deriving (Show, Read, Eq, Ord)
+ deriving (Read, Eq, Ord)
+
+-- These instances are more suitable for diffing
+instance Show CcLink where
+ show CcLink{..} = unlines
+ [ "CcLink"
+ , "{ ccLinkProgram = " ++ show ccLinkProgram
+ , ", ccLinkSupportsNoPie = " ++ show ccLinkSupportsNoPie
+ , ", ccLinkSupportsCompactUnwind = " ++ show ccLinkSupportsCompactUnwind
+ , ", ccLinkSupportsFilelist = " ++ show ccLinkSupportsFilelist
+ , ", ccLinkSupportsResponseFiles = " ++ show ccLinkSupportsResponseFiles
+ , ", ccLinkIsGnu = " ++ show ccLinkIsGnu
+ , "}"
+ ]
findCcLink :: ProgOpt -> Maybe Bool -> ArchOS -> Cc -> Maybe Readelf -> M CcLink
findCcLink progOpt ldOverride archOs cc readelf = checking "for C compiler for linking command" $ do
@@ -95,12 +109,13 @@ checkSupportsNoPie ccLink = checking "whether the cc linker supports -no-pie" $
-- Check output as some GCC versions only warn and don't respect -Werror
-- when passed an unrecognized flag.
(code, out, _err) <- readProgram ccLink ["-no-pie", "-Werror", "-x", "c", test_c, "-o", test]
- if isSuccess code && "unrecognized" `isInfixOf` out
- then return False
- else return True
+ return (isSuccess code && not ("unrecognized" `isInfixOf` out))
checkSupportsCompactUnwind :: Cc -> Program -> M Bool
checkSupportsCompactUnwind cc ccLink = checking "whether the cc linker understands -no_compact_unwind" $
+ -- ROMES:TODO: This returns False here but True in configure because in
+ -- configure we check for ld supports compact unwind, whereas here we check
+ -- for cclink supports compact unwind... what do we need it for?
withTempDir $ \dir -> do
let test_o = dir </> "test.o"
test2_o = dir </> "test2.o"
@@ -108,7 +123,7 @@ checkSupportsCompactUnwind cc ccLink = checking "whether the cc linker understan
compileC cc test_o "int foo() { return 0; }"
exitCode <- runProgram ccLink ["-r", "-no_compact_unwind", "-o", test2_o, test_o]
- pure $ isSuccess exitCode
+ return $ isSuccess exitCode
checkSupportsFilelist :: Cc -> Program -> M Bool
checkSupportsFilelist cc ccLink = checking "whether the cc linker understands -filelist" $
@@ -121,15 +136,17 @@ checkSupportsFilelist cc ccLink = checking "whether the cc linker understands -f
compileC cc test1_o "int foo() { return 0; }"
compileC cc test2_o "int bar() { return 0; }"
- writeFile test_ofiles test1_o -- write the filename test1_o to the test_ofiles file
- appendFile test_ofiles test2_o -- append the filename test2_o to the test_ofiles file
+ -- write the filenames test1_o and test2_o to the test_ofiles file
+ writeFile test_ofiles (unlines [test1_o,test2_o])
exitCode <- runProgram ccLink ["-r", "-filelist", test_ofiles, "-o", test_o]
- pure $ isSuccess exitCode
+ return (isSuccess exitCode)
checkSupportsResponseFiles :: Cc -> Program -> M Bool
checkSupportsResponseFiles cc ccLink = checking "whether the cc linker supports response files" $
+ -- ROMES:TODO: This returns True here while False in configure because in
+ -- configure we call -shared and -dylib on LD, whereas here we do it on CcLink
withTempDir $ \dir -> do
let test_o = dir </> "test.o"
compileC cc test_o "int main(void) {return 0;}"
@@ -141,7 +158,7 @@ checkSupportsResponseFiles cc ccLink = checking "whether the cc linker supports
-- TODO: It'd be good to shortcircuit this logical `or`
exitCode1 <- runProgram ccLink ["-shared", "@"++args_txt]
exitCode2 <- runProgram ccLink ["-dylib", "@"++args_txt]
- pure (isSuccess exitCode1 || isSuccess exitCode2)
+ return (isSuccess exitCode1 || isSuccess exitCode2)
-- | Check whether linking works.
checkLinkWorks :: Cc -> Program -> M ()
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64ef522ca2d655d458d3674bea5ddf0c13f900e4...2bd70e58c1f10ab9aedd6e26f2307f5569f83b8a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64ef522ca2d655d458d3674bea5ddf0c13f900e4...2bd70e58c1f10ab9aedd6e26f2307f5569f83b8a
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/20230605/c9c7928a/attachment-0001.html>
More information about the ghc-commits
mailing list