GCC Middle and Back End API Reference
postreload.cc File Reference
#include "config.h"
#include "system.h"
#include "coretypes.h"
#include "backend.h"
#include "target.h"
#include "rtl.h"
#include "tree.h"
#include "predict.h"
#include "df.h"
#include "memmodel.h"
#include "tm_p.h"
#include "optabs.h"
#include "regs.h"
#include "emit-rtl.h"
#include "recog.h"
#include "cfghooks.h"
#include "cfgrtl.h"
#include "cfgbuild.h"
#include "cfgcleanup.h"
#include "reload.h"
#include "cselib.h"
#include "tree-pass.h"
#include "dbgcnt.h"
#include "function-abi.h"
#include "rtl-iter.h"
Include dependency graph for postreload.cc:

Data Structures

struct  reg_use

Macros

#define RELOAD_COMBINE_MAX_USES   16
#define LABEL_LIVE(LABEL)
#define MODES_OK_FOR_MOVE2ADD(OUTMODE, INMODE)

Functions

static bool reload_cse_simplify (rtx_insn *, rtx)
static void reload_cse_regs_1 (void)
static int reload_cse_simplify_set (rtx, rtx_insn *)
static int reload_cse_simplify_operands (rtx_insn *, rtx)
static void reload_combine (void)
static void reload_combine_note_use (rtx *, rtx_insn *, int, rtx)
static void reload_combine_note_store (rtx, const_rtx, void *)
static bool reload_cse_move2add (rtx_insn *)
static void move2add_note_store (rtx, const_rtx, void *)
static void reload_cse_regs (rtx_insn *first)
static void reload_combine_split_one_ruid (int *pruid, int split_ruid)
static void reload_combine_split_ruids (int split_ruid)
static void reload_combine_purge_insn_uses (rtx_insn *insn)
static void reload_combine_purge_reg_uses_after_ruid (unsigned regno, int ruid)
static struct reg_usereload_combine_closest_single_use (unsigned regno, int ruid_limit)
static void fixup_debug_insns (rtx reg, rtx replacement, rtx_insn *from, rtx_insn *to)
static bool try_replace_in_use (struct reg_use *use, rtx reg, rtx src)
static bool reload_combine_recognize_const_pattern (rtx_insn *insn)
static bool reload_combine_recognize_pattern (rtx_insn *insn)
static void move2add_record_mode (rtx reg)
static void move2add_record_sym_value (rtx reg, rtx sym, rtx off)
static bool move2add_valid_value_p (int regno, scalar_int_mode mode)
static bool move2add_use_add2_insn (scalar_int_mode mode, rtx reg, rtx sym, rtx off, rtx_insn *insn)
static bool move2add_use_add3_insn (scalar_int_mode mode, rtx reg, rtx sym, rtx off, rtx_insn *insn)
static void reload_cse_move2add_invalidate (rtx_insn *insn)
rtl_opt_passmake_pass_postreload_cse (gcc::context *ctxt)

Variables

static struct { ... }  reg_state [FIRST_PSEUDO_REGISTER]
static int reload_combine_ruid
static int last_label_ruid
static int last_jump_ruid
static int first_index_reg = -1
static int last_index_reg
static int reg_set_luid [FIRST_PSEUDO_REGISTER]
static HOST_WIDE_INT reg_offset [FIRST_PSEUDO_REGISTER]
static int reg_base_reg [FIRST_PSEUDO_REGISTER]
static rtx reg_symbol_ref [FIRST_PSEUDO_REGISTER]
static machine_mode reg_mode [FIRST_PSEUDO_REGISTER]
static int move2add_luid
static int move2add_last_label_luid

Macro Definition Documentation

◆ LABEL_LIVE

#define LABEL_LIVE ( LABEL)
Value:
(label_live[CODE_LABEL_NUMBER (LABEL) - min_labelno])
static int min_labelno
Definition final.cc:491
#define CODE_LABEL_NUMBER(INSN)
Definition rtl.h:1673

Referenced by reload_combine().

◆ MODES_OK_FOR_MOVE2ADD

#define MODES_OK_FOR_MOVE2ADD ( OUTMODE,
INMODE )
Value:
(GET_MODE_SIZE (OUTMODE) == GET_MODE_SIZE (INMODE) \
|| (GET_MODE_SIZE (OUTMODE) <= GET_MODE_SIZE (INMODE) \
&& TRULY_NOOP_TRUNCATION_MODES_P (OUTMODE, INMODE)))
ALWAYS_INLINE poly_uint16 GET_MODE_SIZE(machine_mode mode)
Definition machmode.h:657
#define TRULY_NOOP_TRUNCATION_MODES_P(MODE1, MODE2)
Definition machmode.h:1004
??? We don't know how zero / sign extension is handled, hence we can't go from a narrower to a wider mode.

Referenced by move2add_valid_value_p().

◆ RELOAD_COMBINE_MAX_USES

#define RELOAD_COMBINE_MAX_USES   16
If reload couldn't use reg+reg+offset addressing, try to use reg+reg addressing now. This code might also be useful when reload gave up on reg+reg addressing because of clashes between the return register and INDEX_REG_CLASS.
The maximum number of uses of a register we can keep track of to replace them with reg+reg addressing.

Referenced by reload_combine(), reload_combine_closest_single_use(), reload_combine_note_store(), reload_combine_note_use(), reload_combine_purge_insn_uses(), reload_combine_purge_reg_uses_after_ruid(), reload_combine_recognize_pattern(), and reload_combine_split_ruids().

Function Documentation

◆ fixup_debug_insns()

void fixup_debug_insns ( rtx reg,
rtx replacement,
rtx_insn * from,
rtx_insn * to )
static
After we've moved an add insn, fix up any debug insns that occur between the old location of the add and the new location. REG is the destination register of the add insn; REPLACEMENT is the SET_SRC of the add. FROM and TO specify the range in which we should make this change on debug insns.

References DEBUG_BIND_INSN_P, reg_use::insn, INSN_VAR_LOCATION_LOC, NEXT_INSN(), simplify_replace_rtx(), and validate_change().

Referenced by reload_combine_recognize_const_pattern(), and reload_combine_recognize_pattern().

◆ make_pass_postreload_cse()

rtl_opt_pass * make_pass_postreload_cse ( gcc::context * ctxt)

◆ move2add_note_store()

void move2add_note_store ( rtx dst,
const_rtx set,
void * data )
static
SET is a SET or CLOBBER that sets DST. DATA is the insn which contains SET. Update reg_set_luid, reg_offset and reg_base_reg accordingly. Called from reload_cse_move2add via note_stores.

References const0_rtx, CONST_INT_P, find_reg_equal_equiv_note(), gcc_assert, GET_CODE, GET_MODE, INTVAL, invalidate(), is_a(), move2add_last_label_luid, move2add_luid, move2add_record_mode(), move2add_record_sym_value(), move2add_valid_value_p(), NULL_RTX, reg_base_reg, reg_mode, reg_offset, REG_P, reg_set_luid, reg_symbol_ref, REGNO, SET, SET_DEST, SET_SRC, subreg_regno(), trunc_int_for_mode(), UINTVAL, and XEXP.

Referenced by reload_cse_move2add_invalidate().

◆ move2add_record_mode()

void move2add_record_mode ( rtx reg)
static

◆ move2add_record_sym_value()

void move2add_record_sym_value ( rtx reg,
rtx sym,
rtx off )
static
Record that REG is being set to the sum of SYM and OFF.

References INTVAL, move2add_luid, move2add_record_mode(), reg_base_reg, reg_offset, reg_set_luid, reg_symbol_ref, and REGNO.

Referenced by move2add_note_store(), move2add_use_add2_insn(), and move2add_use_add3_insn().

◆ move2add_use_add2_insn()

bool move2add_use_add2_insn ( scalar_int_mode mode,
rtx reg,
rtx sym,
rtx off,
rtx_insn * insn )
static
This function is called with INSN that sets REG (of mode MODE) to (SYM + OFF), while REG is known to already have value (SYM + offset). This function tries to change INSN into an add instruction (set (REG) (plus (REG) (OFF - offset))) using the known value. It also updates the information about REG's known value. Return true if we made a change.

References BLOCK_FOR_INSN(), changed, const0_rtx, costs_lt_p(), FOR_EACH_MODE_UNTIL, gen_int_mode(), gen_lowpart_common(), GET_CODE, get_full_set_rtx_cost(), GET_MODE_MASK, have_add2_insn(), have_insn_for(), reg_use::insn, INTVAL, move2add_record_sym_value(), NULL_RTX, optimize_bb_for_speed_p(), PATTERN(), reg_offset, REGNO, SET_SRC, single_set(), full_rtx_costs::speed, UINTVAL, validate_change(), and XVECEXP.

Referenced by reload_cse_move2add().

◆ move2add_use_add3_insn()

bool move2add_use_add3_insn ( scalar_int_mode mode,
rtx reg,
rtx sym,
rtx off,
rtx_insn * insn )
static
This function is called with INSN that sets REG (of mode MODE) to (SYM + OFF), but REG doesn't have known value (SYM + offset). This function tries to find another register which is known to already have value (SYM + offset) and change INSN into an add instruction (set (REG) (plus (the found register) (OFF - offset))) if such a register is found. It also updates the information about REG's known value. Return true iff we made a change.

References BLOCK_FOR_INSN(), changed, const0_rtx, costs_lt_p(), gen_int_mode(), gen_rtx_REG(), get_full_set_rtx_cost(), GET_MODE, i, init_costs_to_max(), init_costs_to_zero(), move2add_luid, move2add_record_sym_value(), move2add_valid_value_p(), NULL_RTX, optimize_bb_for_speed_p(), reg_base_reg, reg_offset, reg_set_luid, reg_symbol_ref, REGNO, rtx_equal_p(), SET_SRC, single_set(), full_rtx_costs::speed, UINTVAL, validate_change(), and XEXP.

Referenced by reload_cse_move2add().

◆ move2add_valid_value_p()

bool move2add_valid_value_p ( int regno,
scalar_int_mode mode )
static

◆ reload_combine()

◆ reload_combine_closest_single_use()

struct reg_use * reload_combine_closest_single_use ( unsigned regno,
int ruid_limit )
static
Find the use of REGNO with the ruid that is highest among those lower than RUID_LIMIT, and return it if it is the only use of this reg in the insn. Return NULL otherwise.

References i, last_label_ruid, NULL, reg_state, and RELOAD_COMBINE_MAX_USES.

Referenced by reload_combine_recognize_const_pattern().

◆ reload_combine_note_store()

void reload_combine_note_store ( rtx dst,
const_rtx set,
void * data )
static
Check if DST is a register or a subreg of a register; if it is, update store_ruid, real_store_ruid and use_index in the reg_state structure accordingly. Called via note_stores from reload_combine.

References end_hard_regno(), END_REGNO(), GET_CODE, GET_MODE, i, MEM_P, REG_P, reg_state, REGNO, RELOAD_COMBINE_MAX_USES, reload_combine_ruid, SET, SET_DEST, SUBREG_BYTE, SUBREG_REG, subreg_regno_offset(), and XEXP.

Referenced by reload_combine().

◆ reload_combine_note_use()

void reload_combine_note_use ( rtx * xp,
rtx_insn * insn,
int ruid,
rtx containing_mem )
static
XP points to a piece of rtl that has to be checked for any uses of registers. *XP is the pattern of INSN, or a part of it. Called from reload_combine, and recursively by itself.

References rtx_def::code, const0_rtx, CONST_INT_P, reg_use::containing_mem, END_REGNO(), gcc_assert, GET_RTX_FORMAT, GET_RTX_LENGTH, i, reg_use::insn, NULL_RTX, REG_FUNCTION_VALUE_P, REG_NREGS, REG_P, reg_state, REGNO, RELOAD_COMBINE_MAX_USES, reload_combine_note_use(), rtx_equal_p(), reg_use::ruid, SET, SET_DEST, SET_SRC, XEXP, XVECEXP, and XVECLEN.

Referenced by reload_combine(), reload_combine_note_use(), reload_combine_recognize_const_pattern(), and reload_combine_recognize_pattern().

◆ reload_combine_purge_insn_uses()

void reload_combine_purge_insn_uses ( rtx_insn * insn)
static
Called when we are about to rescan a previously encountered insn with reload_combine_note_use after modifying some part of it. This clears all information about uses in that particular insn.

References i, reg_use::insn, reg_state, and RELOAD_COMBINE_MAX_USES.

Referenced by reload_combine_recognize_const_pattern().

◆ reload_combine_purge_reg_uses_after_ruid()

void reload_combine_purge_reg_uses_after_ruid ( unsigned regno,
int ruid )
static
Called when we need to forget about all uses of REGNO after an insn which is identified by RUID.

References reg_state, RELOAD_COMBINE_MAX_USES, and reg_use::ruid.

Referenced by reload_combine_recognize_const_pattern().

◆ reload_combine_recognize_const_pattern()

bool reload_combine_recognize_const_pattern ( rtx_insn * insn)
static
Called by reload_combine when scanning INSN. This function tries to detect patterns where a constant is added to a register, and the result is used in an address. Return true if no further processing is needed on INSN; false if it wasn't recognized and should be handled normally.

References CONSTANT_P, delete_insn(), fixup_debug_insns(), gcc_assert, GET_CODE, GET_MODE, reg_use::insn, use::insn, last_jump_ruid, NULL, NULL_RTX, PATTERN(), REG_NREGS, REG_P, reg_state, REGNO, reload_combine_closest_single_use(), reload_combine_note_use(), reload_combine_purge_insn_uses(), reload_combine_purge_reg_uses_after_ruid(), reload_combine_ruid, reload_combine_split_ruids(), reorder_insns(), rtx_equal_p(), SET_DEST, SET_SRC, single_set(), stack_pointer_rtx, try_replace_in_use(), XEXP, XVECEXP, and XVECLEN.

Referenced by reload_combine().

◆ reload_combine_recognize_pattern()

◆ reload_combine_split_one_ruid()

void reload_combine_split_one_ruid ( int * pruid,
int split_ruid )
inlinestatic
Subroutine of reload_combine_split_ruids, called to fix up a single ruid pointed to by *PRUID if it is higher than SPLIT_RUID.

Referenced by reload_combine_split_ruids().

◆ reload_combine_split_ruids()

void reload_combine_split_ruids ( int split_ruid)
static
Called when we insert a new insn in a position we've already passed in the scan. Examine all our state, increasing all ruids that are higher than SPLIT_RUID by one in order to make room for a new insn.

References i, last_jump_ruid, last_label_ruid, reg_state, RELOAD_COMBINE_MAX_USES, reload_combine_ruid, reload_combine_split_one_ruid(), and reg_use::ruid.

Referenced by reload_combine_recognize_const_pattern().

◆ reload_cse_move2add()

◆ reload_cse_move2add_invalidate()

◆ reload_cse_regs()

void reload_cse_regs ( rtx_insn * first)
static
Call cse / combine like post-reload optimization phases. FIRST is the first instruction.

References reload_combine(), reload_cse_move2add(), and reload_cse_regs_1().

◆ reload_cse_regs_1()

void reload_cse_regs_1 ( void )
static
Do a very simple CSE pass over the hard registers. This function detects no-op moves where we happened to assign two different pseudo-registers to the same hard register, and then copied one to the other. Reload will generate a useless instruction copying a register to itself. This function also detects cases where we load a value from memory into two different registers, and (if memory is more expensive than registers) changes it to simply copy the first register into the second register. Another optimization is performed that scans the operands of each instruction to see whether the value is already available in a hard register. It then replaces the operand with the hard register if possible, much like an optional reload would.

References any_condjump_p(), BB_END, cfg_changed, cfun, cleanup_cfg(), CONST_INT_P, cselib_finish(), cselib_init(), cselib_process_insn(), CSELIB_RECORD_MEMORY, EDGE_COUNT, ei_end_p(), end_alias_analysis(), ENTRY_BLOCK_PTR_FOR_FN, FOR_BB_INSNS, FOR_EACH_BB_FN, FOR_EACH_EDGE, gcc_assert, gen_rtx_REG(), GET_CODE, GET_MODE, GET_MODE_CLASS, init_alias_analysis(), INSN_P, LAST_VIRTUAL_REGISTER, make_insn_raw(), NULL, NULL_RTX, pc_rtx, pc_set(), basic_block_def::preds, REG_P, reg_set_p(), reload_cse_simplify(), rtx_equal_p(), SET_SRC, word_mode, and XEXP.

Referenced by reload_cse_regs().

◆ reload_cse_simplify()

bool reload_cse_simplify ( rtx_insn * insn,
rtx testreg )
static
Perform simple optimizations to clean up the result of reload. Copyright (C) 1987-2025 Free Software Foundation, Inc. This file is part of GCC. GCC is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 3, or (at your option) any later version. GCC is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>.
Try to simplify INSN. Return true if the CFG may have changed.

References apply_change_group(), asm_noperands(), BLOCK_FOR_INSN(), CALL_P, check_for_inc_dec(), CONST_INT_P, count, cselib_invalidate_rtx(), cselib_redundant_set_p(), delete_insn_and_edges(), EDGE_COUNT, GET_CODE, i, NO_FUNCTION_CSE, NULL_RTX, PATTERN(), REG_FUNCTION_VALUE_P, REG_P, reload_cse_simplify_operands(), reload_cse_simplify_set(), SET, SET_DEST, set_dst_reg_note(), set_for_reg_notes(), SET_SRC, stack_pointer_rtx, basic_block_def::succs, value, XEXP, XVECEXP, and XVECLEN.

Referenced by reload_cse_regs_1().

◆ reload_cse_simplify_operands()

int reload_cse_simplify_operands ( rtx_insn * insn,
rtx testreg )
static
Try to replace operands in INSN with equivalent values that are already in registers. This can be viewed as optional reloading. For each non-register operand in the insn, see if any hard regs are known to be equivalent to that operand. Record the alternatives which can accept these hard registers. Among all alternatives, select the ones which are better or equal to the one currently matching, where "better" is in terms of '?' and '!' constraints. Among the remaining alternatives, select the one which replaces most operands with hard registers.

References apply_change_group(), BLOCK_FOR_INSN(), CLEAR_HARD_REG_SET, CONST_INT_P, CONSTANT_P, constraints, cselib_lookup(), extract_constrain_insn(), gcc_assert, gen_rtx_REG(), GET_CODE, GET_MODE, get_preferred_alternatives(), i, LABEL_P, load_extend_op(), elt_loc_list::loc, cselib_val::locs, MEM_P, elt_loc_list::next, NOTE_KIND, NOTE_P, optimize_bb_for_speed_p(), recog_data, REG_CAN_CHANGE_MODE_P, reg_class_subunion, reg_fits_class_p(), REG_P, REGNO, reload_cse_simplify_operands(), SET_DEST, SET_HARD_REG_BIT, set_mode_and_regno(), SET_SRC, set_src_cost(), side_effects_p(), single_set(), TEST_BIT, TEST_HARD_REG_BIT, true_regnum(), validate_change(), which_alternative, and word_mode.

Referenced by reload_cse_simplify(), and reload_cse_simplify_operands().

◆ reload_cse_simplify_set()

int reload_cse_simplify_set ( rtx set,
rtx_insn * insn )
static
Try to simplify a single SET instruction. SET is the set pattern. INSN is the instruction it came from. This function only handles one case: if we set a register to a value which is not a register, we try to find that value in some other register and change the set into a register copy.

References BITS_PER_WORD, BLOCK_FOR_INSN(), CONST_SCALAR_INT_P, CONSTANT_P, cselib_lookup(), wide_int_storage::from(), gcc_unreachable, gen_rtx_REG(), GET_MODE, immed_wide_int_const(), load_extend_op(), elt_loc_list::loc, cselib_val::locs, MEM_P, memory_move_cost(), elt_loc_list::next, optimize_bb_for_speed_p(), ORIGINAL_REGNO, references_value_p(), REG_CAN_CHANGE_MODE_P, REG_P, register_move_cost(), REGNO, SET_DEST, SET_SRC, set_src_cost(), side_effects_p(), SIGNED, true_regnum(), UNSIGNED, validate_change(), validate_unshare_change(), and word_mode.

Referenced by reload_cse_simplify().

◆ try_replace_in_use()

bool try_replace_in_use ( struct reg_use * use,
rtx reg,
rtx src )
static
Subroutine of reload_combine_recognize_const_pattern. Try to replace REG with SRC in the insn described by USE, taking costs into account. Return true if we made the replacement.

References address_cost(), BLOCK_FOR_INSN(), CONSTANT_P, gcc_assert, GET_CODE, GET_MODE, use::insn, MEM_ADDR_SPACE, memory_address_addr_space_p(), NULL_RTX, optimize_bb_for_speed_p(), REG_P, rtx_equal_p(), SET_DEST, SET_SRC, set_src_cost(), simplify_replace_rtx(), single_set(), validate_change(), and XEXP.

Referenced by reload_combine_recognize_const_pattern().

Variable Documentation

◆ first_index_reg

int first_index_reg = -1
static
The register numbers of the first and last index register. A value of -1 in LAST_INDEX_REG indicates that we've previously computed these values and found no suitable index registers.

Referenced by reload_combine(), and reload_combine_recognize_pattern().

◆ last_index_reg

int last_index_reg
static

◆ last_jump_ruid

int last_jump_ruid
static
The RUID of the last jump we encountered in reload_combine.

Referenced by reload_combine(), reload_combine_recognize_const_pattern(), and reload_combine_split_ruids().

◆ last_label_ruid

int last_label_ruid
static
The RUID of the last label we encountered in reload_combine.

Referenced by reload_combine(), reload_combine_closest_single_use(), reload_combine_recognize_pattern(), and reload_combine_split_ruids().

◆ move2add_last_label_luid

int move2add_last_label_luid
static
move2add_last_label_luid is set whenever a label is found. Labels invalidate all previously collected reg_offset data.

Referenced by move2add_note_store(), move2add_valid_value_p(), and reload_cse_move2add().

◆ move2add_luid

int move2add_luid
static
move2add_luid is linearly increased while scanning the instructions from first to last. It is used to set reg_set_luid in reload_cse_move2add and move2add_note_store.

Referenced by move2add_note_store(), move2add_record_sym_value(), move2add_use_add3_insn(), and reload_cse_move2add().

◆ reg_base_reg

int reg_base_reg[FIRST_PSEUDO_REGISTER]
static

◆ reg_mode

◆ reg_offset

HOST_WIDE_INT reg_offset[FIRST_PSEUDO_REGISTER]
static
If reg_base_reg[n] is negative, register n has been set to reg_offset[n] or reg_symbol_ref[n] + reg_offset[n] in mode reg_mode[n]. If reg_base_reg[n] is non-negative, register n has been set to the sum of reg_offset[n] and the value of register reg_base_reg[n] before reg_set_luid[n], calculated in mode reg_mode[n] . For multi-hard-register registers, all but the first one are recorded as BLKmode in reg_mode. Setting reg_mode to VOIDmode marks it as invalid.

Referenced by move2add_note_store(), move2add_record_sym_value(), move2add_use_add2_insn(), move2add_use_add3_insn(), reload_cse_move2add(), and var_lowpart().

◆ reg_set_luid

int reg_set_luid[FIRST_PSEUDO_REGISTER]
static
See if we can reduce the cost of a constant by replacing a move with an add. We track situations in which a register is set to a constant or to a register plus a constant.
We cannot do our optimization across labels. Invalidating all the information about register contents we have would be costly, so we use move2add_last_label_luid to note where the label is and then later disable any optimization that would cross it. reg_offset[n] / reg_base_reg[n] / reg_symbol_ref[n] / reg_mode[n] are only valid if reg_set_luid[n] is greater than move2add_last_label_luid. For a set that established a new (potential) base register with non-constant value, we use move2add_luid from the place where the setting insn is encountered; registers based off that base then get the same reg_set_luid. Constants all get move2add_last_label_luid + 1 as their reg_set_luid.

Referenced by move2add_note_store(), move2add_record_sym_value(), move2add_use_add3_insn(), move2add_valid_value_p(), and reload_cse_move2add().

◆ []

struct { ... } reg_state[FIRST_PSEUDO_REGISTER]
If the register is used in some unknown fashion, USE_INDEX is negative. If it is dead, USE_INDEX is RELOAD_COMBINE_MAX_USES, and STORE_RUID indicates where it is first set or clobbered. Otherwise, USE_INDEX is the index of the last encountered use of the register (which is first among these we have seen since we scan backwards). USE_RUID indicates the first encountered, i.e. last, of these uses. If ALL_OFFSETS_MATCH is true, all encountered uses were inside a PLUS with a constant offset; OFFSET contains this constant in that case. STORE_RUID is always meaningful if we only want to use a value in a register in a different place: it denotes the next insn in the insn stream (i.e. the last encountered) that sets or clobbers the register. REAL_STORE_RUID is similar, but clobbers are ignored when updating it. EXPR is the expression used when storing the register.

Referenced by reload_combine(), reload_combine_closest_single_use(), reload_combine_note_store(), reload_combine_note_use(), reload_combine_purge_insn_uses(), reload_combine_purge_reg_uses_after_ruid(), reload_combine_recognize_const_pattern(), reload_combine_recognize_pattern(), and reload_combine_split_ruids().

◆ reg_symbol_ref

rtx reg_symbol_ref[FIRST_PSEUDO_REGISTER]
static

◆ reload_combine_ruid

int reload_combine_ruid
static
Reverse linear uid. This is increased in reload_combine while scanning the instructions from last to first. It is used to set last_label_ruid and the store_ruid / use_ruid fields in reg_state.

Referenced by reload_combine(), reload_combine_note_store(), reload_combine_recognize_const_pattern(), and reload_combine_split_ruids().