Skip to content
Snippets Groups Projects
Commit b626ebc0 authored by Jakub Jelinek's avatar Jakub Jelinek Committed by Jakub Jelinek
Browse files

cse: Fix up record_jump_equiv checks [PR117095]

The following testcase is miscompiled on s390x-linux with -O2 -march=z15.
The problem happens during cse2, which sees in an extended basic block
(jump_insn 217 78 216 10 (parallel [
            (set (pc)
                (if_then_else (ne (reg:SI 165)
                        (const_int 1 [0x1]))
                    (label_ref 216)
                    (pc)))
            (set (reg:SI 165)
                (plus:SI (reg:SI 165)
                    (const_int -1 [0xffffffffffffffff])))
            (clobber (scratch:SI))
            (clobber (reg:CC 33 %cc))
        ]) "t.c":14:17 discrim 1 2192 {doloop_si64}
     (int_list:REG_BR_PROB 955630228 (nil))
 -> 216)
...
(insn 99 98 100 12 (set (reg:SI 138)
        (const_int 1 [0x1])) "t.c":9:31 1507 {*movsi_zarch}
     (nil))
(insn 100 99 103 12 (parallel [
            (set (reg:SI 137)
                (minus:SI (reg:SI 138)
                    (subreg:SI (reg:HI 135 [ a ]) 0)))
            (clobber (reg:CC 33 %cc))
        ]) "t.c":9:31 1904 {*subsi3}
     (expr_list:REG_DEAD (reg:SI 138)
        (expr_list:REG_DEAD (reg:HI 135 [ a ])
            (expr_list:REG_UNUSED (reg:CC 33 %cc)
                (nil)))))
Note, cse2 has df_note_add_problem () before df_analyze, which add
     (expr_list:REG_UNUSED (reg:SI 165)
        (expr_list:REG_UNUSED (reg:CC 33 %cc)
notes to the first insn (correctly so, %cc is clobbered there and pseudo
165 isn't used after the insn).
Now, cse_extended_basic_block has an extra optimization on conditional
jumps, where it records equivalence on the edge which continues in the ebb.
Here it sees (ne reg:SI 165) (const_int 1) is false on the edge and
remembers that pseudo 165 is comparison equivalent to (const_int 1),
so on insn 100 it decides to replace (reg:SI 138) with (reg:SI 165).

This optimization isn't correct here though, because the JUMP_INSN has
multiple sets.  Before r0-77890 record_jump_equiv has been called from
cse_insn guarded on n_sets == 1 && any_condjump_p (insn), so it wouldn't
be done on the above JUMP_INSN where n_sets == 2.  But since that change
it is guarded with single_set (insn) && any_condjump_p (insn) and that
is true because of the REG_UNUSED note.  Looking at that note is
inappropriate in CSE though, because the whole intent of the pass is to
extend the lifetimes of the pseudos if equivalence is found, so the fact
that there is REG_UNUSED note for (reg:SI 165) and that the reg isn't used
later doesn't imply that it won't be used after the optimization.
So, unless we manage to process the other sets on the JUMP_INSN (it wouldn't
be terribly hard in this exact case, the doloop insn decreases the register
by 1 and so we could just record equivalence to (const_int 0) instead, but
generally it might be hard), we should IMHO just punt if there are multiple
sets.

The patch below adds !multiple_sets (insn) check instead of replacing with
it the single_set (insn) check, because apparently any_condjump_p uses
pc_set which supports the case where PATTERN is a SET to PC (that is a
single_set (insn) && !multiple_sets (insn), PATTERN is a PARALLEL with a
single SET to PC (likewise) and some CLOBBERs, PARALLEL with two or more
SETs where the first one is SET to PC (that could be single_set (insn)
with REG_UNUSED notes but is not !multiple_sets (insn)) or PATTERN
is UNSPEC/UNSPEC_VOLATILE with SET inside of it.  For the last case
!multiple_sets (insn) will be true, but IMHO we shouldn't try to derive
anything from those because we haven't checked the rest of the UNSPEC*
and we don't really know what it does.

2024-12-13  Jakub Jelinek  <jakub@redhat.com>

	PR rtl-optimization/117095
	* cse.cc (cse_extended_basic_block): Don't call record_jump_equiv
	if multiple_sets (insn).

	* gcc.c-torture/execute/pr117095.c: New test.
parent b8314ebf
No related branches found
No related tags found
Loading
Loading
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment