From bd4288c02b487cc8a9afcfa9c21bfe594a78e26d Mon Sep 17 00:00:00 2001
From: Richard Sandiford <richard.sandiford@linaro.org>
Date: Wed, 30 Aug 2017 15:25:38 +0000
Subject: [PATCH] Add a partial_subreg_p predicate

This patch adds a partial_subreg_p predicate to go alongside
paradoxical_subreg_p.

Like the paradoxical_subreg_p patch, this one replaces some tests that
were based on GET_MODE_SIZE rather than GET_MODE_PRECISION.  In each
case the change should be a no-op or an improvement.

The regcprop.c patch prevents some replacements of the 82-bit RFmode
with the 80-bit XFmode on ia64.  I don't understand the target details
here particularly well, but from the way the modes are described in
ia64-modes.def, it isn't valid to assume that an XFmode can carry an
RFmode payload.  A comparison of the testsuite assembly output for one
target per CPU showed no other differences.

Some of the places changed here are tracking the widest access mode
found for a register.  The series tries to standardise on:

  if (partial_subreg_p (widest_seen, new_mode))
    widest_seen = new_mode;

rather than:

  if (paradoxical_subreg_p (new_mode, widest_seen))
    widest_seen = new_mode;

Either would have been OK.

2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
	    Alan Hayward  <alan.hayward@arm.com>
	    David Sherwood  <david.sherwood@arm.com>

gcc/
	* rtl.h (partial_subreg_p): New function.
	* caller-save.c (save_call_clobbered_regs): Use it.
	* calls.c (expand_call): Likewise.
	* combine.c (combinable_i3pat): Likewise.
	(simplify_set): Likewise.
	(make_extraction): Likewise.
	(make_compound_operation_int): Likewise.
	(gen_lowpart_or_truncate): Likewise.
	(force_to_mode): Likewise.
	(make_field_assignment): Likewise.
	(reg_truncated_to_mode): Likewise.
	(record_truncated_value): Likewise.
	(move_deaths): Likewise.
	* cse.c (record_jump_cond): Likewise.
	(cse_insn): Likewise.
	* cselib.c (cselib_lookup_1): Likewise.
	* expmed.c (extract_bit_field_using_extv): Likewise.
	* function.c (assign_parm_setup_reg): Likewise.
	* ifcvt.c (noce_convert_multiple_sets): Likewise.
	* ira-build.c (create_insn_allocnos): Likewise.
	* lra-coalesce.c (merge_pseudos): Likewise.
	* lra-constraints.c (match_reload): Likewise.
	(simplify_operand_subreg): Likewise.
	(curr_insn_transform): Likewise.
	* lra-lives.c (process_bb_lives): Likewise.
	* lra.c (new_insn_reg): Likewise.
	(lra_substitute_pseudo): Likewise.
	* regcprop.c (mode_change_ok): Likewise.
	(maybe_mode_change): Likewise.
	(copyprop_hardreg_forward_1): Likewise.
	* reload.c (push_reload): Likewise.
	(find_reloads): Likewise.
	(find_reloads_subreg_address): Likewise.
	* reload1.c (alter_reg): Likewise.
	(eliminate_regs_1): Likewise.
	* simplify-rtx.c (simplify_unary_operation_1): Likewise.

Co-Authored-By: Alan Hayward <alan.hayward@arm.com>
Co-Authored-By: David Sherwood <david.sherwood@arm.com>

From-SVN: r251536
---
 gcc/ChangeLog         | 41 ++++++++++++++++++++++++++++++++++++
 gcc/caller-save.c     |  3 +--
 gcc/calls.c           |  3 +--
 gcc/combine.c         | 48 +++++++++++++++++++------------------------
 gcc/cse.c             | 25 ++++++++++------------
 gcc/cselib.c          |  4 ++--
 gcc/expmed.c          |  3 +--
 gcc/function.c        |  6 ++----
 gcc/ifcvt.c           |  4 ++--
 gcc/ira-build.c       |  2 +-
 gcc/lra-coalesce.c    |  4 ++--
 gcc/lra-constraints.c | 10 ++++-----
 gcc/lra-lives.c       | 10 ++++-----
 gcc/lra.c             |  6 +++---
 gcc/regcprop.c        | 10 ++++-----
 gcc/reload.c          | 38 +++++++++++++++-------------------
 gcc/reload1.c         |  6 +++---
 gcc/rtl.h             | 24 ++++++++++++++++++++++
 gcc/simplify-rtx.c    |  7 ++-----
 19 files changed, 148 insertions(+), 106 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index d87d910964ba..a726d8e690b8 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,44 @@
+2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
+	    Alan Hayward  <alan.hayward@arm.com>
+	    David Sherwood  <david.sherwood@arm.com>
+
+	* rtl.h (partial_subreg_p): New function.
+	* caller-save.c (save_call_clobbered_regs): Use it.
+	* calls.c (expand_call): Likewise.
+	* combine.c (combinable_i3pat): Likewise.
+	(simplify_set): Likewise.
+	(make_extraction): Likewise.
+	(make_compound_operation_int): Likewise.
+	(gen_lowpart_or_truncate): Likewise.
+	(force_to_mode): Likewise.
+	(make_field_assignment): Likewise.
+	(reg_truncated_to_mode): Likewise.
+	(record_truncated_value): Likewise.
+	(move_deaths): Likewise.
+	* cse.c (record_jump_cond): Likewise.
+	(cse_insn): Likewise.
+	* cselib.c (cselib_lookup_1): Likewise.
+	* expmed.c (extract_bit_field_using_extv): Likewise.
+	* function.c (assign_parm_setup_reg): Likewise.
+	* ifcvt.c (noce_convert_multiple_sets): Likewise.
+	* ira-build.c (create_insn_allocnos): Likewise.
+	* lra-coalesce.c (merge_pseudos): Likewise.
+	* lra-constraints.c (match_reload): Likewise.
+	(simplify_operand_subreg): Likewise.
+	(curr_insn_transform): Likewise.
+	* lra-lives.c (process_bb_lives): Likewise.
+	* lra.c (new_insn_reg): Likewise.
+	(lra_substitute_pseudo): Likewise.
+	* regcprop.c (mode_change_ok): Likewise.
+	(maybe_mode_change): Likewise.
+	(copyprop_hardreg_forward_1): Likewise.
+	* reload.c (push_reload): Likewise.
+	(find_reloads): Likewise.
+	(find_reloads_subreg_address): Likewise.
+	* reload1.c (alter_reg): Likewise.
+	(eliminate_regs_1): Likewise.
+	* simplify-rtx.c (simplify_unary_operation_1): Likewise.
+
 2017-08-30  David Edelsohn  <dje.gcc@gmail.com>
 
 	* config/rs6000/rs6000.c (rs6000_expand_binop_builtin): Revert
diff --git a/gcc/caller-save.c b/gcc/caller-save.c
index 27da129ab9ca..65a498d0d0cc 100644
--- a/gcc/caller-save.c
+++ b/gcc/caller-save.c
@@ -837,8 +837,7 @@ save_call_clobbered_regs (void)
 		  nregs = hard_regno_nregs[r][PSEUDO_REGNO_MODE (regno)];
 		  mode = HARD_REGNO_CALLER_SAVE_MODE
 		    (r, nregs, PSEUDO_REGNO_MODE (regno));
-		  if (GET_MODE_BITSIZE (mode)
-		      > GET_MODE_BITSIZE (save_mode[r]))
+		  if (partial_subreg_p (save_mode[r], mode))
 		    save_mode[r] = mode;
 		  while (nregs-- > 0)
 		    SET_HARD_REG_BIT (hard_regs_to_save, r + nregs);
diff --git a/gcc/calls.c b/gcc/calls.c
index d5bd5049cb94..79b6e25ac9ad 100644
--- a/gcc/calls.c
+++ b/gcc/calls.c
@@ -3357,8 +3357,7 @@ expand_call (tree exp, rtx target, int ignore)
 	      || ((caller_mode != caller_promoted_mode
 		   || callee_mode != callee_promoted_mode)
 		  && (caller_unsignedp != callee_unsignedp
-		      || GET_MODE_BITSIZE (caller_mode)
-			 < GET_MODE_BITSIZE (callee_mode)))))
+		      || partial_subreg_p (caller_mode, callee_mode)))))
 	{
 	  try_tail_call = 0;
 	  maybe_complain_about_tail_call (exp,
diff --git a/gcc/combine.c b/gcc/combine.c
index bc31280ec3be..86055385d78f 100644
--- a/gcc/combine.c
+++ b/gcc/combine.c
@@ -2224,9 +2224,7 @@ combinable_i3pat (rtx_insn *i3, rtx *loc, rtx i2dest, rtx i1dest, rtx i0dest,
 	 STACK_POINTER_REGNUM, since these are always considered to be
 	 live.  Similarly for ARG_POINTER_REGNUM if it is fixed.  */
       subdest = dest;
-      if (GET_CODE (subdest) == SUBREG
-	  && (GET_MODE_SIZE (GET_MODE (subdest))
-	      >= GET_MODE_SIZE (GET_MODE (SUBREG_REG (subdest)))))
+      if (GET_CODE (subdest) == SUBREG && !partial_subreg_p (subdest))
 	subdest = SUBREG_REG (subdest);
       if (pi3dest_killed
 	  && REG_P (subdest)
@@ -6882,10 +6880,8 @@ simplify_set (rtx x)
   /* If we have (set (cc0) (subreg ...)), we try to remove the subreg
      in SRC.  */
   if (dest == cc0_rtx
-      && GET_CODE (src) == SUBREG
-      && subreg_lowpart_p (src)
-      && (GET_MODE_PRECISION (GET_MODE (src))
-	  < GET_MODE_PRECISION (GET_MODE (SUBREG_REG (src)))))
+      && partial_subreg_p (src)
+      && subreg_lowpart_p (src))
     {
       rtx inner = SUBREG_REG (src);
       machine_mode inner_mode = GET_MODE (inner);
@@ -7634,7 +7630,7 @@ make_extraction (machine_mode mode, rtx inner, HOST_WIDE_INT pos,
   /* Never narrow an object, since that might not be safe.  */
 
   if (mode != VOIDmode
-      && GET_MODE_SIZE (extraction_mode) < GET_MODE_SIZE (mode))
+      && partial_subreg_p (extraction_mode, mode))
     extraction_mode = mode;
 
   if (!MEM_P (inner))
@@ -7681,7 +7677,7 @@ make_extraction (machine_mode mode, rtx inner, HOST_WIDE_INT pos,
   if (wanted_inner_mode != VOIDmode
       && inner_mode != wanted_inner_mode
       && ! pos_rtx
-      && GET_MODE_SIZE (wanted_inner_mode) < GET_MODE_SIZE (is_mode)
+      && partial_subreg_p (wanted_inner_mode, is_mode)
       && MEM_P (inner)
       && ! mode_dependent_address_p (XEXP (inner, 0), MEM_ADDR_SPACE (inner))
       && ! MEM_VOLATILE_P (inner))
@@ -8201,7 +8197,7 @@ make_compound_operation_int (scalar_int_mode mode, rtx *x_ptr,
 		   to (subreg:QI (lshiftrt:SI (reg:SI) (const_int 7)) 0).  */
 		|| (GET_CODE (inner) == AND
 		    && CONST_INT_P (XEXP (inner, 1))
-		    && GET_MODE_SIZE (mode) < GET_MODE_SIZE (GET_MODE (inner))
+		    && partial_subreg_p (x)
 		    && exact_log2 (UINTVAL (XEXP (inner, 1)))
 		       >= GET_MODE_BITSIZE (mode) - 1)))
 	  subreg_code = SET;
@@ -8214,7 +8210,7 @@ make_compound_operation_int (scalar_int_mode mode, rtx *x_ptr,
 	  tem = simplified;
 
 	if (GET_CODE (tem) != GET_CODE (inner)
-	    && GET_MODE_SIZE (mode) < GET_MODE_SIZE (GET_MODE (inner))
+	    && partial_subreg_p (x)
 	    && subreg_lowpart_p (x))
 	  {
 	    rtx newer
@@ -8225,8 +8221,9 @@ make_compound_operation_int (scalar_int_mode mode, rtx *x_ptr,
 	    if (GET_CODE (newer) != SUBREG)
 	      newer = make_compound_operation (newer, in_code);
 
-	    /* force_to_mode can expand compounds.  If it just re-expanded the
-	       compound, use gen_lowpart to convert to the desired mode.  */
+	    /* force_to_mode can expand compounds.  If it just re-expanded
+	       the compound, use gen_lowpart to convert to the desired
+	       mode.  */
 	    if (rtx_equal_p (newer, x)
 		/* Likewise if it re-expanded the compound only partially.
 		   This happens for SUBREG of ZERO_EXTRACT if they extract
@@ -8468,7 +8465,7 @@ static rtx
 gen_lowpart_or_truncate (machine_mode mode, rtx x)
 {
   if (!CONST_INT_P (x)
-      && GET_MODE_SIZE (mode) < GET_MODE_SIZE (GET_MODE (x))
+      && partial_subreg_p (mode, GET_MODE (x))
       && !TRULY_NOOP_TRUNCATION_MODES_P (mode, GET_MODE (x))
       && !(REG_P (x) && reg_truncated_to_mode (mode, x)))
     {
@@ -8523,7 +8520,7 @@ force_to_mode (rtx x, machine_mode mode, unsigned HOST_WIDE_INT mask,
   /* It is not valid to do a right-shift in a narrower mode
      than the one it came in with.  */
   if ((code == LSHIFTRT || code == ASHIFTRT)
-      && GET_MODE_PRECISION (mode) < GET_MODE_PRECISION (GET_MODE (x)))
+      && partial_subreg_p (mode, GET_MODE (x)))
     op_mode = GET_MODE (x);
 
   /* Truncate MASK to fit OP_MODE.  */
@@ -8560,8 +8557,7 @@ force_to_mode (rtx x, machine_mode mode, unsigned HOST_WIDE_INT mask,
      if the constant masks to zero all the bits the mode doesn't have.  */
   if (GET_CODE (x) == SUBREG
       && subreg_lowpart_p (x)
-      && ((GET_MODE_SIZE (GET_MODE (x))
-	   < GET_MODE_SIZE (GET_MODE (SUBREG_REG (x))))
+      && (partial_subreg_p (x)
 	  || (0 == (mask
 		    & GET_MODE_MASK (GET_MODE (x))
 		    & ~GET_MODE_MASK (GET_MODE (SUBREG_REG (x)))))))
@@ -9555,8 +9551,7 @@ make_field_assignment (rtx x)
 
   if (GET_CODE (src) == AND && GET_CODE (XEXP (src, 0)) == SUBREG
       && subreg_lowpart_p (XEXP (src, 0))
-      && (GET_MODE_SIZE (GET_MODE (XEXP (src, 0)))
-	  < GET_MODE_SIZE (GET_MODE (SUBREG_REG (XEXP (src, 0)))))
+      && partial_subreg_p (XEXP (src, 0))
       && GET_CODE (SUBREG_REG (XEXP (src, 0))) == ROTATE
       && CONST_INT_P (XEXP (SUBREG_REG (XEXP (src, 0)), 0))
       && INTVAL (XEXP (SUBREG_REG (XEXP (src, 0)), 0)) == -2
@@ -13325,7 +13320,7 @@ reg_truncated_to_mode (machine_mode mode, const_rtx x)
   if (truncated == 0
       || rsp->truncation_label < label_tick_ebb_start)
     return false;
-  if (GET_MODE_SIZE (truncated) <= GET_MODE_SIZE (mode))
+  if (!partial_subreg_p (mode, truncated))
     return true;
   if (TRULY_NOOP_TRUNCATION_MODES_P (mode, truncated))
     return true;
@@ -13348,9 +13343,10 @@ record_truncated_value (rtx x)
       machine_mode original_mode = GET_MODE (SUBREG_REG (x));
       truncated_mode = GET_MODE (x);
 
-      if (GET_MODE_SIZE (original_mode) <= GET_MODE_SIZE (truncated_mode))
+      if (!partial_subreg_p (truncated_mode, original_mode))
 	return true;
 
+      truncated_mode = GET_MODE (x);
       if (TRULY_NOOP_TRUNCATION_MODES_P (truncated_mode, original_mode))
 	return true;
 
@@ -13366,8 +13362,7 @@ record_truncated_value (rtx x)
   rsp = &reg_stat[REGNO (x)];
   if (rsp->truncated_to_mode == 0
       || rsp->truncation_label < label_tick_ebb_start
-      || (GET_MODE_SIZE (truncated_mode)
-	  < GET_MODE_SIZE (rsp->truncated_to_mode)))
+      || partial_subreg_p (truncated_mode, rsp->truncated_to_mode))
     {
       rsp->truncated_to_mode = truncated_mode;
       rsp->truncation_label = label_tick;
@@ -13891,8 +13886,7 @@ move_deaths (rtx x, rtx maybe_kill_insn, int from_luid, rtx_insn *to_insn,
 	     the remaining registers in place of NOTE.  */
 
 	  if (note != 0 && regno < FIRST_PSEUDO_REGISTER
-	      && (GET_MODE_SIZE (GET_MODE (XEXP (note, 0)))
-		  > GET_MODE_SIZE (GET_MODE (x))))
+	      && partial_subreg_p (GET_MODE (x), GET_MODE (XEXP (note, 0))))
 	    {
 	      unsigned int deadregno = REGNO (XEXP (note, 0));
 	      unsigned int deadend = END_REGNO (XEXP (note, 0));
@@ -13911,8 +13905,8 @@ move_deaths (rtx x, rtx maybe_kill_insn, int from_luid, rtx_insn *to_insn,
 	     their own REG_DEAD notes lying around.  */
 	  else if ((note == 0
 		    || (note != 0
-			&& (GET_MODE_SIZE (GET_MODE (XEXP (note, 0)))
-			    < GET_MODE_SIZE (GET_MODE (x)))))
+			&& partial_subreg_p (GET_MODE (XEXP (note, 0)),
+					     GET_MODE (x))))
 		   && regno < FIRST_PSEUDO_REGISTER
 		   && REG_NREGS (x) > 1)
 	    {
diff --git a/gcc/cse.c b/gcc/cse.c
index 34ea3d22f547..672fd2eaea97 100644
--- a/gcc/cse.c
+++ b/gcc/cse.c
@@ -3953,10 +3953,9 @@ record_jump_cond (enum rtx_code code, machine_mode mode, rtx op0,
      if we test MODE instead, we can get an infinite recursion
      alternating between two modes each wider than MODE.  */
 
-  if (code == NE && GET_CODE (op0) == SUBREG
-      && subreg_lowpart_p (op0)
-      && (GET_MODE_SIZE (GET_MODE (op0))
-	  < GET_MODE_SIZE (GET_MODE (SUBREG_REG (op0)))))
+  if (code == NE
+      && partial_subreg_p (op0)
+      && subreg_lowpart_p (op0))
     {
       machine_mode inner_mode = GET_MODE (SUBREG_REG (op0));
       rtx tem = record_jump_cond_subreg (inner_mode, op1);
@@ -3965,10 +3964,9 @@ record_jump_cond (enum rtx_code code, machine_mode mode, rtx op0,
 			  reversed_nonequality);
     }
 
-  if (code == NE && GET_CODE (op1) == SUBREG
-      && subreg_lowpart_p (op1)
-      && (GET_MODE_SIZE (GET_MODE (op1))
-	  < GET_MODE_SIZE (GET_MODE (SUBREG_REG (op1)))))
+  if (code == NE
+      && partial_subreg_p (op1)
+      && subreg_lowpart_p (op1))
     {
       machine_mode inner_mode = GET_MODE (SUBREG_REG (op1));
       rtx tem = record_jump_cond_subreg (inner_mode, op0);
@@ -5013,8 +5011,8 @@ cse_insn (rtx_insn *insn)
 	      && ! (src != 0
 		    && GET_CODE (src) == SUBREG
 		    && GET_MODE (src) == GET_MODE (p->exp)
-		    && (GET_MODE_SIZE (GET_MODE (SUBREG_REG (src)))
-			< GET_MODE_SIZE (GET_MODE (SUBREG_REG (p->exp))))))
+		    && partial_subreg_p (GET_MODE (SUBREG_REG (src)),
+					 GET_MODE (SUBREG_REG (p->exp)))))
 	    continue;
 
 	  if (src && GET_CODE (src) == code && rtx_equal_p (src, p->exp))
@@ -5124,8 +5122,8 @@ cse_insn (rtx_insn *insn)
 	      && ! (src != 0
 		    && GET_CODE (src) == SUBREG
 		    && GET_MODE (src) == GET_MODE (elt->exp)
-		    && (GET_MODE_SIZE (GET_MODE (SUBREG_REG (src)))
-			< GET_MODE_SIZE (GET_MODE (SUBREG_REG (elt->exp))))))
+		    && partial_subreg_p (GET_MODE (SUBREG_REG (src)),
+					 GET_MODE (SUBREG_REG (elt->exp)))))
 	    {
 	      elt = elt->next_same_value;
 	      continue;
@@ -5967,8 +5965,7 @@ cse_insn (rtx_insn *insn)
 	    && (((GET_MODE_SIZE (GET_MODE (SUBREG_REG (dest))) - 1)
 		 / UNITS_PER_WORD)
 		== (GET_MODE_SIZE (GET_MODE (dest)) - 1) / UNITS_PER_WORD)
-	    && (GET_MODE_SIZE (GET_MODE (dest))
-		>= GET_MODE_SIZE (GET_MODE (SUBREG_REG (dest))))
+	    && !partial_subreg_p (dest)
 	    && sets[i].src_elt != 0)
 	  {
 	    machine_mode new_mode = GET_MODE (SUBREG_REG (dest));
diff --git a/gcc/cselib.c b/gcc/cselib.c
index 41e0e4fbb341..d20e4bb662b4 100644
--- a/gcc/cselib.c
+++ b/gcc/cselib.c
@@ -2035,8 +2035,8 @@ cselib_lookup_1 (rtx x, machine_mode mode,
 	    if (is_int_mode (GET_MODE (l->elt->val_rtx), &lmode)
 		&& GET_MODE_SIZE (lmode) > GET_MODE_SIZE (int_mode)
 		&& (lwider == NULL
-		    || GET_MODE_SIZE (lmode)
-		       < GET_MODE_SIZE (GET_MODE (lwider->elt->val_rtx))))
+		    || partial_subreg_p (lmode,
+					 GET_MODE (lwider->elt->val_rtx))))
 	      {
 		struct elt_loc_list *el;
 		if (i < FIRST_PSEUDO_REGISTER
diff --git a/gcc/expmed.c b/gcc/expmed.c
index f38fb3177709..ff9eb5b2c71d 100644
--- a/gcc/expmed.c
+++ b/gcc/expmed.c
@@ -1528,8 +1528,7 @@ extract_bit_field_using_extv (const extraction_insn *extv, rtx op0,
 	  && TRULY_NOOP_TRUNCATION_MODES_P (GET_MODE (target), ext_mode))
 	{
 	  target = gen_lowpart (ext_mode, target);
-	  if (GET_MODE_PRECISION (ext_mode)
-	      > GET_MODE_PRECISION (GET_MODE (spec_target)))
+	  if (partial_subreg_p (GET_MODE (spec_target), ext_mode))
 	    spec_target_subreg = target;
 	}
       else
diff --git a/gcc/function.c b/gcc/function.c
index 4c77e19973e1..7d952e7994b4 100644
--- a/gcc/function.c
+++ b/gcc/function.c
@@ -3262,13 +3262,11 @@ assign_parm_setup_reg (struct assign_parm_data_all *all, tree parm,
       push_to_sequence2 (all->first_conversion_insn, all->last_conversion_insn);
       tempreg = convert_to_mode (data->nominal_mode, tempreg, unsignedp);
 
-      if (GET_CODE (tempreg) == SUBREG
+      if (partial_subreg_p (tempreg)
 	  && GET_MODE (tempreg) == data->nominal_mode
 	  && REG_P (SUBREG_REG (tempreg))
 	  && data->nominal_mode == data->passed_mode
-	  && GET_MODE (SUBREG_REG (tempreg)) == GET_MODE (data->entry_parm)
-	  && GET_MODE_SIZE (GET_MODE (tempreg))
-	     < GET_MODE_SIZE (GET_MODE (data->entry_parm)))
+	  && GET_MODE (SUBREG_REG (tempreg)) == GET_MODE (data->entry_parm))
 	{
 	  /* The argument is already sign/zero extended, so note it
 	     into the subreg.  */
diff --git a/gcc/ifcvt.c b/gcc/ifcvt.c
index 9a646a692987..e1b163cd42ee 100644
--- a/gcc/ifcvt.c
+++ b/gcc/ifcvt.c
@@ -3198,7 +3198,7 @@ noce_convert_multiple_sets (struct noce_if_info *if_info)
 	{
 	  machine_mode src_mode = GET_MODE (new_val);
 	  machine_mode dst_mode = GET_MODE (temp);
-	  if (GET_MODE_SIZE (src_mode) <= GET_MODE_SIZE (dst_mode))
+	  if (!partial_subreg_p (dst_mode, src_mode))
 	    {
 	      end_sequence ();
 	      return FALSE;
@@ -3209,7 +3209,7 @@ noce_convert_multiple_sets (struct noce_if_info *if_info)
 	{
 	  machine_mode src_mode = GET_MODE (old_val);
 	  machine_mode dst_mode = GET_MODE (temp);
-	  if (GET_MODE_SIZE (src_mode) <= GET_MODE_SIZE (dst_mode))
+	  if (!partial_subreg_p (dst_mode, src_mode))
 	    {
 	      end_sequence ();
 	      return FALSE;
diff --git a/gcc/ira-build.c b/gcc/ira-build.c
index 308a286a1f20..5c428539e9c9 100644
--- a/gcc/ira-build.c
+++ b/gcc/ira-build.c
@@ -1853,7 +1853,7 @@ create_insn_allocnos (rtx x, rtx outer, bool output_p)
 	      if (outer != NULL && GET_CODE (outer) == SUBREG)
 		{
 		  machine_mode wmode = GET_MODE (outer);
-		  if (GET_MODE_SIZE (wmode) > GET_MODE_SIZE (ALLOCNO_WMODE (a)))
+		  if (partial_subreg_p (ALLOCNO_WMODE (a), wmode))
 		    ALLOCNO_WMODE (a) = wmode;
 		}
 	    }
diff --git a/gcc/lra-coalesce.c b/gcc/lra-coalesce.c
index 44887b19e1f6..7af10d8d2648 100644
--- a/gcc/lra-coalesce.c
+++ b/gcc/lra-coalesce.c
@@ -112,8 +112,8 @@ merge_pseudos (int regno1, int regno2)
     = (lra_merge_live_ranges
        (lra_reg_info[first].live_ranges,
 	lra_copy_live_range_list (lra_reg_info[first2].live_ranges)));
-  if (GET_MODE_SIZE (lra_reg_info[first].biggest_mode)
-      < GET_MODE_SIZE (lra_reg_info[first2].biggest_mode))
+  if (partial_subreg_p (lra_reg_info[first].biggest_mode,
+			lra_reg_info[first2].biggest_mode))
     lra_reg_info[first].biggest_mode = lra_reg_info[first2].biggest_mode;
 }
 
diff --git a/gcc/lra-constraints.c b/gcc/lra-constraints.c
index 3ebc803ed957..6da910e33a87 100644
--- a/gcc/lra-constraints.c
+++ b/gcc/lra-constraints.c
@@ -928,7 +928,7 @@ match_reload (signed char out, signed char *ins, signed char *outs,
   push_to_sequence (*before);
   if (inmode != outmode)
     {
-      if (GET_MODE_SIZE (inmode) > GET_MODE_SIZE (outmode))
+      if (partial_subreg_p (outmode, inmode))
 	{
 	  reg = new_in_reg
 	    = lra_create_new_reg_with_unique_value (inmode, in_rtx,
@@ -1579,8 +1579,7 @@ simplify_operand_subreg (int nop, machine_mode reg_mode)
 	      bitmap_set_bit (&lra_subreg_reload_pseudos, REGNO (new_reg));
 
 	      insert_before = (type != OP_OUT
-			       || GET_MODE_SIZE (innermode)
-				    > GET_MODE_SIZE (mode));
+			       || partial_subreg_p (mode, innermode));
 	      insert_after = type != OP_IN;
 	      insert_move_for_subreg (insert_before ? &before : NULL,
 				      insert_after ? &after : NULL,
@@ -3939,8 +3938,7 @@ curr_insn_transform (bool check_only_p)
       lra_assert (out >= 0 && in >= 0
 		  && curr_static_id->operand[out].type == OP_OUT
 		  && curr_static_id->operand[in].type == OP_IN);
-      rld = (GET_MODE_SIZE (GET_MODE (dest)) <= GET_MODE_SIZE (GET_MODE (src))
-	     ? dest : src);
+      rld = partial_subreg_p (GET_MODE (src), GET_MODE (dest)) ? src : dest;
       rld_mode = GET_MODE (rld);
 #ifdef SECONDARY_MEMORY_NEEDED_MODE
       sec_mode = SECONDARY_MEMORY_NEEDED_MODE (rld_mode);
@@ -3950,7 +3948,7 @@ curr_insn_transform (bool check_only_p)
       new_reg = lra_create_new_reg (sec_mode, NULL_RTX,
 				    NO_REGS, "secondary");
       /* If the mode is changed, it should be wider.  */
-      lra_assert (GET_MODE_SIZE (sec_mode) >= GET_MODE_SIZE (rld_mode));
+      lra_assert (!partial_subreg_p (sec_mode, rld_mode));
       if (sec_mode != rld_mode)
         {
 	  /* If the target says specifically to use another mode for
diff --git a/gcc/lra-lives.c b/gcc/lra-lives.c
index e728e348215f..8650dc7fca75 100644
--- a/gcc/lra-lives.c
+++ b/gcc/lra-lives.c
@@ -717,9 +717,9 @@ process_bb_lives (basic_block bb, int &curr_point, bool dead_insn_p)
       for (reg = curr_id->regs; reg != NULL; reg = reg->next)
 	{
 	  int i, regno = reg->regno;
-	  
-	  if (GET_MODE_SIZE (reg->biggest_mode)
-	      > GET_MODE_SIZE (lra_reg_info[regno].biggest_mode))
+
+	  if (partial_subreg_p (lra_reg_info[regno].biggest_mode,
+				reg->biggest_mode))
 	    lra_reg_info[regno].biggest_mode = reg->biggest_mode;
 	  if (regno < FIRST_PSEUDO_REGISTER)
 	    {
@@ -729,8 +729,8 @@ process_bb_lives (basic_block bb, int &curr_point, bool dead_insn_p)
 		 part of multi-register group.  Process this case
 		 here.  */
 	      for (i = 1; i < hard_regno_nregs[regno][reg->biggest_mode]; i++)
-		if (GET_MODE_SIZE (GET_MODE (regno_reg_rtx[regno + i]))
-		    > GET_MODE_SIZE (lra_reg_info[regno + i].biggest_mode))
+		if (partial_subreg_p (lra_reg_info[regno + i].biggest_mode,
+				      GET_MODE (regno_reg_rtx[regno + i])))
 		  lra_reg_info[regno + i].biggest_mode
 		    = GET_MODE (regno_reg_rtx[regno + i]);
 	    }
diff --git a/gcc/lra.c b/gcc/lra.c
index affec0c5948d..61e40eebe3ff 100644
--- a/gcc/lra.c
+++ b/gcc/lra.c
@@ -546,8 +546,8 @@ new_insn_reg (rtx_insn *insn, int regno, enum op_type type,
   lra_insn_reg *ir = lra_insn_reg_pool.allocate ();
   ir->type = type;
   ir->biggest_mode = mode;
-  if (GET_MODE_SIZE (mode) > GET_MODE_SIZE (lra_reg_info[regno].biggest_mode)
-      && NONDEBUG_INSN_P (insn))
+  if (NONDEBUG_INSN_P (insn)
+      && partial_subreg_p (lra_reg_info[regno].biggest_mode, mode))
     lra_reg_info[regno].biggest_mode = mode;
   ir->subreg_p = subreg_p;
   ir->early_clobber = early_clobber;
@@ -1913,7 +1913,7 @@ lra_substitute_pseudo (rtx *loc, int old_regno, rtx new_reg, bool subreg_p)
       if (mode != inner_mode
 	  && ! (CONST_INT_P (new_reg) && SCALAR_INT_MODE_P (mode)))
 	{
-	  if (GET_MODE_SIZE (mode) >= GET_MODE_SIZE (inner_mode)
+	  if (!partial_subreg_p (mode, inner_mode)
 	      || ! SCALAR_INT_MODE_P (inner_mode))
 	    new_reg = gen_rtx_SUBREG (mode, new_reg, 0);
 	  else
diff --git a/gcc/regcprop.c b/gcc/regcprop.c
index 367d85a7e242..0d4ec172aee2 100644
--- a/gcc/regcprop.c
+++ b/gcc/regcprop.c
@@ -372,7 +372,7 @@ static bool
 mode_change_ok (machine_mode orig_mode, machine_mode new_mode,
 		unsigned int regno ATTRIBUTE_UNUSED)
 {
-  if (GET_MODE_SIZE (orig_mode) < GET_MODE_SIZE (new_mode))
+  if (partial_subreg_p (orig_mode, new_mode))
     return false;
 
 #ifdef CANNOT_CHANGE_MODE_CLASS
@@ -392,8 +392,8 @@ maybe_mode_change (machine_mode orig_mode, machine_mode copy_mode,
 		   machine_mode new_mode, unsigned int regno,
 		   unsigned int copy_regno ATTRIBUTE_UNUSED)
 {
-  if (GET_MODE_SIZE (copy_mode) < GET_MODE_SIZE (orig_mode)
-      && GET_MODE_SIZE (copy_mode) < GET_MODE_SIZE (new_mode))
+  if (partial_subreg_p (copy_mode, orig_mode)
+      && partial_subreg_p (copy_mode, new_mode))
     return NULL_RTX;
 
   /* Avoid creating multiple copies of the stack pointer.  Some ports
@@ -1076,8 +1076,8 @@ copyprop_hardreg_forward_1 (basic_block bb, struct value_data *vd)
       /* If a noop move is using narrower mode than we have recorded,
 	 we need to either remove the noop move, or kill_set_value.  */
       if (noop_p
-	  && (GET_MODE_BITSIZE (GET_MODE (SET_DEST (set)))
-	      < GET_MODE_BITSIZE (vd->e[REGNO (SET_DEST (set))].mode)))
+	  && partial_subreg_p (GET_MODE (SET_DEST (set)),
+			       vd->e[REGNO (SET_DEST (set))].mode))
 	{
 	  if (noop_move_p (insn))
 	    {
diff --git a/gcc/reload.c b/gcc/reload.c
index 2116332b55aa..e0793cff8b9d 100644
--- a/gcc/reload.c
+++ b/gcc/reload.c
@@ -1071,8 +1071,7 @@ push_reload (rtx in, rtx out, rtx *inloc, rtx *outloc,
 		      && paradoxical_subreg_p (inmode, inner_mode)
 		      && LOAD_EXTEND_OP (inner_mode) != UNKNOWN)
 		  || (WORD_REGISTER_OPERATIONS
-		      && (GET_MODE_PRECISION (inmode)
-			  < GET_MODE_PRECISION (GET_MODE (SUBREG_REG (in))))
+		      && partial_subreg_p (inmode, GET_MODE (SUBREG_REG (in)))
 		      && ((GET_MODE_SIZE (inmode) - 1) / UNITS_PER_WORD ==
 			  ((GET_MODE_SIZE (GET_MODE (SUBREG_REG (in))) - 1)
 			   / UNITS_PER_WORD)))))
@@ -1171,8 +1170,7 @@ push_reload (rtx in, rtx out, rtx *inloc, rtx *outloc,
 	       || MEM_P (SUBREG_REG (out)))
 	      && (paradoxical_subreg_p (outmode, GET_MODE (SUBREG_REG (out)))
 		  || (WORD_REGISTER_OPERATIONS
-		      && (GET_MODE_PRECISION (outmode)
-			  < GET_MODE_PRECISION (GET_MODE (SUBREG_REG (out))))
+		      && partial_subreg_p (outmode, GET_MODE (SUBREG_REG (out)))
 		      && ((GET_MODE_SIZE (outmode) - 1) / UNITS_PER_WORD ==
 			  ((GET_MODE_SIZE (GET_MODE (SUBREG_REG (out))) - 1)
 			   / UNITS_PER_WORD)))))
@@ -1417,10 +1415,10 @@ push_reload (rtx in, rtx out, rtx *inloc, rtx *outloc,
       /* The modes can be different.  If they are, we want to reload in
 	 the larger mode, so that the value is valid for both modes.  */
       if (inmode != VOIDmode
-	  && GET_MODE_SIZE (inmode) > GET_MODE_SIZE (rld[i].inmode))
+	  && partial_subreg_p (rld[i].inmode, inmode))
 	rld[i].inmode = inmode;
       if (outmode != VOIDmode
-	  && GET_MODE_SIZE (outmode) > GET_MODE_SIZE (rld[i].outmode))
+	  && partial_subreg_p (rld[i].outmode, outmode))
 	rld[i].outmode = outmode;
       if (in != 0)
 	{
@@ -1462,26 +1460,25 @@ push_reload (rtx in, rtx out, rtx *inloc, rtx *outloc,
 	     overwrite the operands only when the new mode is larger.
 	     See also PR33613.  */
 	  if (!rld[i].in
-	      || GET_MODE_SIZE (GET_MODE (in))
-	           > GET_MODE_SIZE (GET_MODE (rld[i].in)))
+	      || partial_subreg_p (GET_MODE (rld[i].in), GET_MODE (in)))
 	    rld[i].in = in;
 	  if (!rld[i].in_reg
 	      || (in_reg
-		  && GET_MODE_SIZE (GET_MODE (in_reg))
-	             > GET_MODE_SIZE (GET_MODE (rld[i].in_reg))))
+		  && partial_subreg_p (GET_MODE (rld[i].in_reg),
+				       GET_MODE (in_reg))))
 	    rld[i].in_reg = in_reg;
 	}
       if (out != 0)
 	{
 	  if (!rld[i].out
 	      || (out
-		  && GET_MODE_SIZE (GET_MODE (out))
-	             > GET_MODE_SIZE (GET_MODE (rld[i].out))))
+		  && partial_subreg_p (GET_MODE (rld[i].out),
+				       GET_MODE (out))))
 	    rld[i].out = out;
 	  if (outloc
 	      && (!rld[i].out_reg
-		  || GET_MODE_SIZE (GET_MODE (*outloc))
-		     > GET_MODE_SIZE (GET_MODE (rld[i].out_reg))))
+		  || partial_subreg_p (GET_MODE (rld[i].out_reg),
+				       GET_MODE (*outloc))))
 	    rld[i].out_reg = *outloc;
 	}
       if (reg_class_subset_p (rclass, rld[i].rclass))
@@ -1587,7 +1584,7 @@ push_reload (rtx in, rtx out, rtx *inloc, rtx *outloc,
       int regno;
       machine_mode rel_mode = inmode;
 
-      if (out && GET_MODE_SIZE (outmode) > GET_MODE_SIZE (inmode))
+      if (out && partial_subreg_p (rel_mode, outmode))
 	rel_mode = outmode;
 
       for (note = REG_NOTES (this_insn); note; note = XEXP (note, 1))
@@ -4554,11 +4551,10 @@ find_reloads (rtx_insn *insn, int replace, int ind_levels, int live_known,
   /* Compute reload_mode and reload_nregs.  */
   for (i = 0; i < n_reloads; i++)
     {
-      rld[i].mode
-	= (rld[i].inmode == VOIDmode
-	   || (GET_MODE_SIZE (rld[i].outmode)
-	       > GET_MODE_SIZE (rld[i].inmode)))
-	  ? rld[i].outmode : rld[i].inmode;
+      rld[i].mode = rld[i].inmode;
+      if (rld[i].mode == VOIDmode
+	  || partial_subreg_p (rld[i].mode, rld[i].outmode))
+	rld[i].mode = rld[i].outmode;
 
       rld[i].nregs = ira_reg_class_max_nregs [rld[i].rclass][rld[i].mode];
     }
@@ -6162,7 +6158,7 @@ find_reloads_subreg_address (rtx x, int opnum, enum reload_type type,
     return NULL;
 
   if (WORD_REGISTER_OPERATIONS
-      && GET_MODE_SIZE (outer_mode) < GET_MODE_SIZE (inner_mode)
+      && partial_subreg_p (outer_mode, inner_mode)
       && ((GET_MODE_SIZE (outer_mode) - 1) / UNITS_PER_WORD
           == (GET_MODE_SIZE (inner_mode) - 1) / UNITS_PER_WORD))
     return NULL;
diff --git a/gcc/reload1.c b/gcc/reload1.c
index 6666344a39b1..023eaeea63e3 100644
--- a/gcc/reload1.c
+++ b/gcc/reload1.c
@@ -2218,8 +2218,8 @@ alter_reg (int i, int from_reg, bool dont_share_p)
 
 	  if (spill_stack_slot[from_reg])
 	    {
-	      if (GET_MODE_SIZE (GET_MODE (spill_stack_slot[from_reg]))
-		  > inherent_size)
+	      if (partial_subreg_p (mode,
+				    GET_MODE (spill_stack_slot[from_reg])))
 		mode = GET_MODE (spill_stack_slot[from_reg]);
 	      if (spill_stack_slot_width[from_reg] > total_size)
 		total_size = spill_stack_slot_width[from_reg];
@@ -2817,7 +2817,7 @@ eliminate_regs_1 (rtx x, machine_mode mem_mode, rtx insn,
 	  int new_size = GET_MODE_SIZE (GET_MODE (new_rtx));
 
 	  if (MEM_P (new_rtx)
-	      && ((x_size < new_size
+	      && ((partial_subreg_p (GET_MODE (x), GET_MODE (new_rtx))
 		   /* On RISC machines, combine can create rtl of the form
 		      (set (subreg:m1 (reg:m2 R) 0) ...)
 		      where m1 < m2, and expects something interesting to
diff --git a/gcc/rtl.h b/gcc/rtl.h
index b8ba49fe2c5b..79abfa35fb44 100644
--- a/gcc/rtl.h
+++ b/gcc/rtl.h
@@ -2823,6 +2823,30 @@ extern rtx operand_subword_force (rtx, unsigned int, machine_mode);
 extern int subreg_lowpart_p (const_rtx);
 extern unsigned int subreg_size_lowpart_offset (unsigned int, unsigned int);
 
+/* Return true if a subreg of mode OUTERMODE would only access part of
+   an inner register with mode INNERMODE.  The other bits of the inner
+   register would then be "don't care" on read.  The behavior for writes
+   depends on REGMODE_NATURAL_SIZE; bits in the same REGMODE_NATURAL_SIZE-d
+   chunk would be clobbered but other bits would be preserved.  */
+
+inline bool
+partial_subreg_p (machine_mode outermode, machine_mode innermode)
+{
+  return GET_MODE_PRECISION (outermode) < GET_MODE_PRECISION (innermode);
+}
+
+/* Likewise return true if X is a subreg that is smaller than the inner
+   register.  Use df_read_modify_subreg_p to test whether writing to such
+   a subreg preserves any part of the inner register.  */
+
+inline bool
+partial_subreg_p (const_rtx x)
+{
+  if (GET_CODE (x) != SUBREG)
+    return false;
+  return partial_subreg_p (GET_MODE (x), GET_MODE (SUBREG_REG (x)));
+}
+
 /* Return true if a subreg with the given outer and inner modes is
    paradoxical.  */
 
diff --git a/gcc/simplify-rtx.c b/gcc/simplify-rtx.c
index 60ea9a12f573..6f4398e06ff4 100644
--- a/gcc/simplify-rtx.c
+++ b/gcc/simplify-rtx.c
@@ -995,10 +995,8 @@ simplify_unary_operation_1 (enum rtx_code code, machine_mode mode, rtx op)
 					XEXP (op, 0), const0_rtx);
 
 
-      if (GET_CODE (op) == SUBREG
+      if (partial_subreg_p (op)
 	  && subreg_lowpart_p (op)
-	  && (GET_MODE_SIZE (GET_MODE (op))
-	      < GET_MODE_SIZE (GET_MODE (SUBREG_REG (op))))
 	  && GET_CODE (SUBREG_REG (op)) == ASHIFT
 	  && XEXP (SUBREG_REG (op), 0) == const1_rtx)
 	{
@@ -1640,10 +1638,9 @@ simplify_unary_operation_1 (enum rtx_code code, machine_mode mode, rtx op)
 	 of mode N.  E.g.
 	 (zero_extend:SI (subreg:QI (and:SI (reg:SI) (const_int 63)) 0)) is
 	 (and:SI (reg:SI) (const_int 63)).  */
-      if (GET_CODE (op) == SUBREG
+      if (partial_subreg_p (op)
 	  && is_a <scalar_int_mode> (mode, &int_mode)
 	  && is_a <scalar_int_mode> (GET_MODE (SUBREG_REG (op)), &op0_mode)
-	  && GET_MODE_PRECISION (GET_MODE (op)) < GET_MODE_PRECISION (op0_mode)
 	  && GET_MODE_PRECISION (op0_mode) <= HOST_BITS_PER_WIDE_INT
 	  && GET_MODE_PRECISION (int_mode) >= GET_MODE_PRECISION (op0_mode)
 	  && subreg_lowpart_p (op)
-- 
GitLab