[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: configure: Use LDFLAGS when trying linkers
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Mar 26 18:56:10 UTC 2024
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
b25725ec by Rodrigo Mesquita at 2024-03-26T14:56:01-04:00
configure: Use LDFLAGS when trying linkers
A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we
will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to
check for a working linker. If either of these fail, we try the next in
line.
However, we were not considering the `$LDFLAGS` when checking if these
linkers worked. So we would pick a linker that does not support the
current $LDFLAGS and fail further down the line when we used that linker
with those flags.
Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not
supported by `ld.gold` but that was being picked still.
- - - - -
3300d2b4 by Rodrigo Mesquita at 2024-03-26T14:56:02-04:00
bindist: Clean xattrs of bin and lib at configure time
For issue #21506, we started cleaning the extended attributes of
binaries and libraries from the bindist *after* they were installed to
workaround notarisation (#17418), as part of `make install`.
However, the `ghc-toolchain` binary that is now shipped with the bindist
must be run at `./configure` time. Since we only cleaned the xattributes
of the binaries and libs after they were installed, in some situations
users would be unable to run `ghc-toolchain` from the bindist, failing
at configure time (#24554).
In this commit we move the xattr cleaning logic to the configure script.
Fixes #24554
- - - - -
e1e7a132 by Rodrigo Mesquita at 2024-03-26T14:56:02-04:00
Revert "NCG: Fix a bug in jump shortcutting."
This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66.
Fixes #24586
- - - - -
15 changed files:
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- m4/fp_cc_linker_flag_try.m4
- − testsuite/tests/codeGen/should_run/T24507.hs
- − testsuite/tests/codeGen/should_run/T24507.stdout
- − testsuite/tests/codeGen/should_run/T24507_cmm.cmm
- testsuite/tests/codeGen/should_run/all.T
Changes:
=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -301,20 +301,15 @@ isJumpishInstr instr = case instr of
-- | Checks whether this instruction is a jump/branch instruction.
-- One that can change the flow of control in a way that the
-- register allocator needs to worry about.
-jumpDestsOfInstr :: Instr -> [Maybe BlockId]
+jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i
-jumpDestsOfInstr i = case i of
- (CBZ _ t) -> [ mkDest t ]
- (CBNZ _ t) -> [ mkDest t ]
- (J t) -> [ mkDest t ]
- (B t) -> [ mkDest t ]
- (BL t _ _) -> [ mkDest t ]
- (BCOND _ t) -> [ mkDest t ]
- _ -> []
- where
- mkDest (TBlock id) = Just id
- mkDest TLabel{} = Nothing
- mkDest TReg{} = Nothing
+jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr (J t) = [id | TBlock id <- [t]]
+jumpDestsOfInstr (B t) = [id | TBlock id <- [t]]
+jumpDestsOfInstr (BL t _ _) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr _ = []
-- | Change the destination of this jump instruction.
-- Used in the linear allocator when adding fixup blocks for join
=====================================
compiler/GHC/CmmToAsm/BlockLayout.hs
=====================================
@@ -771,7 +771,7 @@ dropJumps :: forall a i. Instruction i => LabelMap a -> [GenBasicBlock i]
dropJumps _ [] = []
dropJumps info (BasicBlock lbl ins:todo)
| Just ins <- nonEmpty ins --This can happen because of shortcutting
- , [Just dest] <- jumpDestsOfInstr (NE.last ins)
+ , [dest] <- jumpDestsOfInstr (NE.last ins)
, BasicBlock nextLbl _ : _ <- todo
, not (mapMember dest info)
, nextLbl == dest
@@ -870,7 +870,7 @@ mkNode edgeWeights block@(BasicBlock id instrs) =
| length successors > 2 || edgeWeight info <= 0 -> []
| otherwise -> [target]
| Just instr <- lastMaybe instrs
- , [one] <- jumpBlockDestsOfInstr instr
+ , [one] <- jumpDestsOfInstr instr
= [one]
| otherwise = []
=====================================
compiler/GHC/CmmToAsm/Instr.hs
=====================================
@@ -17,8 +17,6 @@ import GHC.Cmm.BlockId
import GHC.CmmToAsm.Config
import GHC.Data.FastString
-import Data.Maybe (catMaybes)
-
-- | Holds a list of source and destination registers used by a
-- particular instruction.
--
@@ -75,17 +73,9 @@ class Instruction instr where
-- | Give the possible destinations of this jump instruction.
-- Must be defined for all jumpish instructions.
- -- Returns Nothing for non BlockId destinations.
jumpDestsOfInstr
- :: instr -> [Maybe BlockId]
-
- -- | Give the possible block destinations of this jump instruction.
- -- Must be defined for all jumpish instructions.
- jumpBlockDestsOfInstr
:: instr -> [BlockId]
- jumpBlockDestsOfInstr = catMaybes . jumpDestsOfInstr
-
-- | Change the destination of this jump instruction.
-- Used in the linear allocator when adding fixup blocks for join
=====================================
compiler/GHC/CmmToAsm/PPC/Instr.hs
=====================================
@@ -513,15 +513,12 @@ isJumpishInstr instr
-- | Checks whether this instruction is a jump/branch instruction.
-- One that can change the flow of control in a way that the
-- register allocator needs to worry about.
-jumpDestsOfInstr :: Instr -> [Maybe BlockId]
+jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr insn
= case insn of
- BCC _ id _ -> [Just id]
- BCCFAR _ id _ -> [Just id]
- BCTR targets _ _ -> targets
- BCTRL{} -> [Nothing]
- BL{} -> [Nothing]
- JMP{} -> [Nothing]
+ BCC _ id _ -> [id]
+ BCCFAR _ id _ -> [id]
+ BCTR targets _ _ -> [id | Just id <- targets]
_ -> []
=====================================
compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
=====================================
@@ -207,7 +207,7 @@ cleanForward platform blockId assoc acc (li : instrs)
-- Remember the association over a jump.
| LiveInstr instr _ <- li
- , targets <- jumpBlockDestsOfInstr instr
+ , targets <- jumpDestsOfInstr instr
, not $ null targets
= do mapM_ (accJumpValid assoc) targets
cleanForward platform blockId assoc (li : acc) instrs
@@ -386,7 +386,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs)
-- it always does, but if those reloads are cleaned the slot
-- liveness map doesn't get updated.
| LiveInstr instr _ <- li
- , targets <- jumpBlockDestsOfInstr instr
+ , targets <- jumpDestsOfInstr instr
= do
let slotsReloadedByTargets
= IntSet.unions
=====================================
compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
=====================================
@@ -57,7 +57,7 @@ joinToTargets block_live id instr
= return ([], instr)
| otherwise
- = joinToTargets' block_live [] id instr (jumpBlockDestsOfInstr instr)
+ = joinToTargets' block_live [] id instr (jumpDestsOfInstr instr)
-----
joinToTargets'
=====================================
compiler/GHC/CmmToAsm/Reg/Liveness.hs
=====================================
@@ -468,7 +468,7 @@ slurpReloadCoalesce live
-- if we hit a jump, remember the current slotMap
| LiveInstr (Instr instr) _ <- li
- , targets <- jumpBlockDestsOfInstr instr
+ , targets <- jumpDestsOfInstr instr
, not $ null targets
= do mapM_ (accSlotMap slotMap) targets
return (slotMap, Nothing)
@@ -760,7 +760,7 @@ sccBlocks blocks entries mcfg = map (fmap node_payload) sccs
sccs = stronglyConnCompG g2
getOutEdges :: Instruction instr => [instr] -> [BlockId]
- getOutEdges instrs = concatMap jumpBlockDestsOfInstr instrs
+ getOutEdges instrs = concatMap jumpDestsOfInstr instrs
-- This is truly ugly, but I don't see a good alternative.
-- Digraph just has the wrong API. We want to identify nodes
@@ -837,7 +837,7 @@ checkIsReverseDependent sccs'
slurpJumpDestsOfBlock (BasicBlock _ instrs)
= unionManyUniqSets
- $ map (mkUniqSet . jumpBlockDestsOfInstr)
+ $ map (mkUniqSet . jumpDestsOfInstr)
[ i | LiveInstr i _ <- instrs]
@@ -1047,7 +1047,7 @@ liveness1 platform liveregs blockmap (LiveInstr instr _)
-- union in the live regs from all the jump destinations of this
-- instruction.
- targets = jumpBlockDestsOfInstr instr -- where we go from here
+ targets = jumpDestsOfInstr instr -- where we go from here
not_a_branch = null targets
targetLiveRegs target
=====================================
compiler/GHC/CmmToAsm/X86/Instr.hs
=====================================
@@ -672,16 +672,13 @@ isJumpishInstr instr
jumpDestsOfInstr
:: Instr
- -> [Maybe BlockId]
+ -> [BlockId]
jumpDestsOfInstr insn
= case insn of
- JXX _ id -> [Just id]
- JMP_TBL _ ids _ _ -> [(mkDest dest) | Just dest <- ids]
+ JXX _ id -> [id]
+ JMP_TBL _ ids _ _ -> [id | Just (DestBlockId id) <- ids]
_ -> []
- where
- mkDest (DestBlockId id) = Just id
- mkDest _ = Nothing
patchJumpInstr
=====================================
distrib/configure.ac.in
=====================================
@@ -105,6 +105,29 @@ if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO"; then
FP_SETUP_WINDOWS_TOOLCHAIN([$hardtop/mingw/], [\$\$topdir/../mingw/])
fi
+
+if test "$HostOS" = "darwin"; then
+ # On darwin, we need to clean the extended attributes of the
+ # ghc-toolchain binary and its dynamic library before we can execute it in the bindist
+ # (this is a workaround for #24554, for the lack of proper notarisation #17418)
+
+ # The following is the work around suggested by @carter in #17418 during
+ # install time. This should help us with code signing issues by removing
+ # extended attributes from all files.
+ XATTR=${XATTR:-/usr/bin/xattr}
+
+ if [ -e "${XATTR}" ]; then
+
+ # Instead of cleaning the attributes of the ghc-toolchain binary only,
+ # we clean them from all files in the bin/ and lib/ directories, as it additionally future
+ # proofs running executables from the bindist besides ghc-toolchain at configure time, and
+ # we can avoid figuring out the path to the ghc-toolchain dynlib specifically.
+ /usr/bin/xattr -rc bin/
+ /usr/bin/xattr -rc lib/
+
+ fi
+fi
+
dnl ** Which gcc to use?
dnl --------------------------------------------------------------
AC_PROG_CC([gcc clang])
=====================================
hadrian/bindist/Makefile
=====================================
@@ -19,13 +19,6 @@ default:
# TODO : find if a better function exists
eq=$(and $(findstring $(1),$(2)),$(findstring $(2),$(1)))
-# the following is the work around suggested by @carter in #17418 during install
-# time. This should help us with code signing issues by removing extended
-# attributes from all files.
-ifeq "$(Darwin_Host)" "YES"
-XATTR ?= /usr/bin/xattr
-endif
-
# patchpackageconf
#
# Hacky function to patch up the 'haddock-interfaces' and 'haddock-html'
@@ -157,10 +150,6 @@ install_bin_libdir:
$(INSTALL_PROGRAM) "$$i" "$(DESTDIR)$(ActualBinsDir)"; \
fi; \
done
- # Work around #17418 on Darwin
- if [ -e "${XATTR}" ]; then \
- "${XATTR}" -c -r "$(DESTDIR)$(ActualBinsDir)"; \
- fi
.PHONY: install_bin_direct
install_bin_direct:
@@ -195,10 +184,6 @@ install_lib: lib/settings
$(INSTALL_DATA) $$i "$$dest/`dirname $$i`" ;; \
esac; \
done; \
- # Work around #17418 on Darwin
- if [ -e "${XATTR}" ]; then \
- "${XATTR}" -c -r "$(DESTDIR)$(ActualLibsDir)"; \
- fi
.PHONY: install_docs
install_docs:
=====================================
m4/fp_cc_linker_flag_try.m4
=====================================
@@ -9,7 +9,7 @@
AC_DEFUN([FP_CC_LINKER_FLAG_TRY], [
AC_MSG_CHECKING([whether C compiler supports -fuse-ld=$1])
echo 'int main(void) {return 0;}' > conftest.c
- if $CC -o conftest.o -fuse-ld=$1 conftest.c > /dev/null 2>&1
+ if $CC -o conftest.o -fuse-ld=$1 $LDFLAGS conftest.c > /dev/null 2>&1
then
$2="-fuse-ld=$1"
AC_MSG_RESULT([yes])
=====================================
testsuite/tests/codeGen/should_run/T24507.hs deleted
=====================================
@@ -1,15 +0,0 @@
-{-# LANGUAGE MagicHash #-}
-{-# LANGUAGE UnboxedTuples #-}
-{-# LANGUAGE GHCForeignImportPrim #-}
-{-# LANGUAGE UnliftedFFITypes #-}
-
-module Main where
-
-import GHC.Exts
-
-foreign import prim "foo" foo :: Int# -> Int#
-
-main = do
-
- let f x = case x of I# x' -> case foo x' of x -> print (I# x)
- mapM_ f [1..7]
\ No newline at end of file
=====================================
testsuite/tests/codeGen/should_run/T24507.stdout deleted
=====================================
@@ -1,7 +0,0 @@
-1
-2
-2
-2
-2
-2
-2
=====================================
testsuite/tests/codeGen/should_run/T24507_cmm.cmm deleted
=====================================
@@ -1,35 +0,0 @@
-#include "Cmm.h"
-
-bar() {
- return (2);
-}
-
-foo(W_ x) {
-
- switch(x) {
- case 1: goto a;
- case 2: goto b;
- case 3: goto c;
- case 4: goto d;
- case 5: goto e;
- case 6: goto f;
- case 7: goto g;
- }
- return (1);
-
- a:
- return (1);
- b:
- jump bar();
- c:
- jump bar();
- d:
- jump bar();
- e:
- jump bar();
- f:
- jump bar();
- g:
- jump bar();
-
-}
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -243,6 +243,3 @@ test('MulMayOflo_full',
test('T24264run', normal, compile_and_run, [''])
test('T24295a', normal, compile_and_run, ['-O -floopification'])
test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms'])
-
-test('T24507', [req_cmm], multi_compile_and_run,
- ['T24507', [('T24507_cmm.cmm', '')], '-O2'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0fcc5b8433fad7b479c21b270e96d9a1cd45c939...e1e7a13281bc69e1a02d78ce4c5874e7cf2e3b54
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0fcc5b8433fad7b479c21b270e96d9a1cd45c939...e1e7a13281bc69e1a02d78ce4c5874e7cf2e3b54
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/20240326/c43f97cf/attachment-0001.html>
More information about the ghc-commits
mailing list