[Git][ghc/ghc][wip/toolchain-selection] Fixes to match configure output
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Mon Jun 5 21:54:10 UTC 2023
Rodrigo Mesquita pushed to branch wip/toolchain-selection at Glasgow Haskell Compiler / GHC
Commits:
64ef522c by Rodrigo Mesquita at 2023-06-05T22:53:59+01:00
Fixes to match configure output
- - - - -
3 changed files:
- utils/ghc-toolchain/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
Changes:
=====================================
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)]
@@ -329,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
@@ -340,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/Tools/Link.hs
=====================================
@@ -109,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"
@@ -122,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" $
@@ -135,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;}"
@@ -155,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/-/commit/64ef522ca2d655d458d3674bea5ddf0c13f900e4
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64ef522ca2d655d458d3674bea5ddf0c13f900e4
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/6893bdf6/attachment-0001.html>
More information about the ghc-commits
mailing list