This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[patch] rtlanal.c: Remove unused functions.


Hi,

Attached is a patch to remove unused functions in rtlanal.c.

These functions are somewhat new, a little more than a year old.
Please remind me if you plan to use any of these functions in future.

Tested on i686-pc-linux-gnu.  OK to apply?

Kazu Hirata

2003-11-27  Kazu Hirata  <kazu@cs.umass.edu>

	* basic-block.h: Remove corresponding prototypes.
	* rtl.h: Likewise.
	* rtlanal.c (can_hoist_insn_p): Remove.
	(hoist_insn_after): Likewise.
	(hoist_insn_to_edge): Likewise.
	(get_jump_table_offset): Likewise.
	(reg_referenced_between_p): Likewise.
	(no_jumps_between_p): Likewise.
	(insn_dependent_p): Likewise.
	(reg_set_last): Likewise.
	(insn_dependent_p_1): Likewise.
	(hoist_test_store): Likewise.
	(hoist_update_store): Likewise.

Index: basic-block.h
===================================================================
RCS file: /cvs/gcc/gcc/gcc/basic-block.h,v
retrieving revision 1.183
diff -u -r1.183 basic-block.h
--- basic-block.h	18 Jul 2003 22:52:05 -0000	1.183
+++ basic-block.h	30 Nov 2003 16:32:07 -0000
@@ -596,9 +596,6 @@
 extern void set_edge_can_fallthru_flag (void);
 extern void update_br_prob_note (basic_block);
 extern void fixup_abnormal_edges (void);
-extern bool can_hoist_insn_p (rtx, rtx, regset);
-extern rtx hoist_insn_after (rtx, rtx, rtx, rtx);
-extern rtx hoist_insn_to_edge (rtx, edge, rtx, rtx);
 extern bool inside_basic_block_p (rtx);
 extern bool control_flow_insn_p (rtx);
 
Index: rtl.h
===================================================================
RCS file: /cvs/gcc/gcc/gcc/rtl.h,v
retrieving revision 1.439
diff -u -r1.439 rtl.h
--- rtl.h	29 Nov 2003 01:13:43 -0000	1.439
+++ rtl.h	30 Nov 2003 16:32:09 -0000
@@ -1667,22 +1667,18 @@
 extern int rtx_addr_varies_p (rtx, int);
 extern HOST_WIDE_INT get_integer_term (rtx);
 extern rtx get_related_value (rtx);
-extern rtx get_jump_table_offset (rtx, rtx *);
 extern int global_reg_mentioned_p (rtx);
 extern int reg_mentioned_p (rtx, rtx);
 extern int count_occurrences (rtx, rtx, int);
 extern int reg_referenced_p (rtx, rtx);
 extern int reg_used_between_p (rtx, rtx, rtx);
-extern int reg_referenced_between_p (rtx, rtx, rtx);
 extern int reg_set_between_p (rtx, rtx, rtx);
 extern int regs_set_between_p (rtx, rtx, rtx);
 extern int commutative_operand_precedence (rtx);
 extern int swap_commutative_operands_p (rtx, rtx);
 extern int modified_between_p (rtx, rtx, rtx);
 extern int no_labels_between_p (rtx, rtx);
-extern int no_jumps_between_p (rtx, rtx);
 extern int modified_in_p (rtx, rtx);
-extern int insn_dependent_p (rtx, rtx);
 extern int reg_set_p (rtx, rtx);
 extern rtx single_set_2 (rtx, rtx);
 extern int multiple_sets (rtx);
@@ -1694,7 +1690,6 @@
 extern rtx set_of (rtx, rtx);
 extern void note_stores (rtx, void (*) (rtx, rtx, void *), void *);
 extern void note_uses (rtx *, void (*) (rtx *, void *), void *);
-extern rtx reg_set_last (rtx, rtx);
 extern int dead_or_set_p (rtx, rtx);
 extern int dead_or_set_regno_p (rtx, unsigned int);
 extern rtx find_reg_note (rtx, enum reg_note, rtx);
Index: rtlanal.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/rtlanal.c,v
retrieving revision 1.169
diff -u -r1.169 rtlanal.c
--- rtlanal.c	18 Oct 2003 18:45:16 -0000	1.169
+++ rtlanal.c	30 Nov 2003 16:32:10 -0000
@@ -37,12 +37,9 @@
 /* Forward declarations */
 static int global_reg_mentioned_p_1 (rtx *, void *);
 static void set_of_1 (rtx, rtx, void *);
-static void insn_dependent_p_1 (rtx, rtx, void *);
 static int rtx_referenced_p_1 (rtx *, void *);
 static int computed_jump_p_1 (rtx);
 static void parms_set (rtx, rtx, void *);
-static bool hoist_test_store (rtx, rtx, regset);
-static void hoist_update_store (rtx, rtx *, rtx, rtx);
 
 /* Bit flags that specify the machine subtype we are compiling for.
    Bits are tested using macros TARGET_... defined in the tm.h file
@@ -435,138 +432,6 @@
   return 0;
 }
 
-/* Given a tablejump insn INSN, return the RTL expression for the offset
-   into the jump table.  If the offset cannot be determined, then return
-   NULL_RTX.
-
-   If EARLIEST is nonzero, it is a pointer to a place where the earliest
-   insn used in locating the offset was found.  */
-
-rtx
-get_jump_table_offset (rtx insn, rtx *earliest)
-{
-  rtx label;
-  rtx table;
-  rtx set;
-  rtx old_insn;
-  rtx x;
-  rtx old_x;
-  rtx y;
-  rtx old_y;
-  int i;
-
-  if (!tablejump_p (insn, &label, &table) || !(set = single_set (insn)))
-    return NULL_RTX;
-
-  x = SET_SRC (set);
-
-  /* Some targets (eg, ARM) emit a tablejump that also
-     contains the out-of-range target.  */
-  if (GET_CODE (x) == IF_THEN_ELSE
-      && GET_CODE (XEXP (x, 2)) == LABEL_REF)
-    x = XEXP (x, 1);
-
-  /* Search backwards and locate the expression stored in X.  */
-  for (old_x = NULL_RTX; GET_CODE (x) == REG && x != old_x;
-       old_x = x, x = find_last_value (x, &insn, NULL_RTX, 0))
-    ;
-
-  /* If X is an expression using a relative address then strip
-     off the addition / subtraction of PC, PIC_OFFSET_TABLE_REGNUM,
-     or the jump table label.  */
-  if (GET_CODE (PATTERN (table)) == ADDR_DIFF_VEC
-      && (GET_CODE (x) == PLUS || GET_CODE (x) == MINUS))
-    {
-      for (i = 0; i < 2; i++)
-	{
-	  old_insn = insn;
-	  y = XEXP (x, i);
-
-	  if (y == pc_rtx || y == pic_offset_table_rtx)
-	    break;
-
-	  for (old_y = NULL_RTX; GET_CODE (y) == REG && y != old_y;
-	       old_y = y, y = find_last_value (y, &old_insn, NULL_RTX, 0))
-	    ;
-
-	  if ((GET_CODE (y) == LABEL_REF && XEXP (y, 0) == label))
-	    break;
-	}
-
-      if (i >= 2)
-	return NULL_RTX;
-
-      x = XEXP (x, 1 - i);
-
-      for (old_x = NULL_RTX; GET_CODE (x) == REG && x != old_x;
-	   old_x = x, x = find_last_value (x, &insn, NULL_RTX, 0))
-	;
-    }
-
-  /* Strip off any sign or zero extension.  */
-  if (GET_CODE (x) == SIGN_EXTEND || GET_CODE (x) == ZERO_EXTEND)
-    {
-      x = XEXP (x, 0);
-
-      for (old_x = NULL_RTX; GET_CODE (x) == REG && x != old_x;
-	   old_x = x, x = find_last_value (x, &insn, NULL_RTX, 0))
-	;
-    }
-
-  /* If X isn't a MEM then this isn't a tablejump we understand.  */
-  if (GET_CODE (x) != MEM)
-    return NULL_RTX;
-
-  /* Strip off the MEM.  */
-  x = XEXP (x, 0);
-
-  for (old_x = NULL_RTX; GET_CODE (x) == REG && x != old_x;
-       old_x = x, x = find_last_value (x, &insn, NULL_RTX, 0))
-    ;
-
-  /* If X isn't a PLUS than this isn't a tablejump we understand.  */
-  if (GET_CODE (x) != PLUS)
-    return NULL_RTX;
-
-  /* At this point we should have an expression representing the jump table
-     plus an offset.  Examine each operand in order to determine which one
-     represents the jump table.  Knowing that tells us that the other operand
-     must represent the offset.  */
-  for (i = 0; i < 2; i++)
-    {
-      old_insn = insn;
-      y = XEXP (x, i);
-
-      for (old_y = NULL_RTX; GET_CODE (y) == REG && y != old_y;
-	   old_y = y, y = find_last_value (y, &old_insn, NULL_RTX, 0))
-	;
-
-      if ((GET_CODE (y) == CONST || GET_CODE (y) == LABEL_REF)
-	  && reg_mentioned_p (label, y))
-	break;
-    }
-
-  if (i >= 2)
-    return NULL_RTX;
-
-  x = XEXP (x, 1 - i);
-
-  /* Strip off the addition / subtraction of PIC_OFFSET_TABLE_REGNUM.  */
-  if (GET_CODE (x) == PLUS || GET_CODE (x) == MINUS)
-    for (i = 0; i < 2; i++)
-      if (XEXP (x, i) == pic_offset_table_rtx)
-	{
-	  x = XEXP (x, 1 - i);
-	  break;
-	}
-
-  if (earliest)
-    *earliest = insn;
-
-  /* Return the RTL expression representing the offset.  */
-  return x;
-}
-
 /* A subroutine of global_reg_mentioned_p, returns 1 if *LOC mentions
    a global register.  */
 
@@ -782,19 +647,6 @@
   return 1;
 }
 
-/* Return 1 if in between BEG and END, exclusive of BEG and END, there is
-   no JUMP_INSN insn.  */
-
-int
-no_jumps_between_p (rtx beg, rtx end)
-{
-  rtx p;
-  for (p = NEXT_INSN (beg); p != end; p = NEXT_INSN (p))
-    if (GET_CODE (p) == JUMP_INSN)
-      return 0;
-  return 1;
-}
-
 /* Nonzero if register REG is used in an insn between
    FROM_INSN and TO_INSN (exclusive of those two).  */
 
@@ -892,27 +744,6 @@
       return 0;
     }
 }
-
-/* Nonzero if register REG is referenced in an insn between
-   FROM_INSN and TO_INSN (exclusive of those two).  Sets of REG do
-   not count.  */
-
-int
-reg_referenced_between_p (rtx reg, rtx from_insn, rtx to_insn)
-{
-  rtx insn;
-
-  if (from_insn == to_insn)
-    return 0;
-
-  for (insn = NEXT_INSN (from_insn); insn != to_insn; insn = NEXT_INSN (insn))
-    if (INSN_P (insn)
-	&& (reg_referenced_p (reg, PATTERN (insn))
-	   || (GET_CODE (insn) == CALL_INSN
-	      && find_reg_fusage (insn, USE, reg))))
-      return 1;
-  return 0;
-}
 
 /* Nonzero if register REG is set or clobbered in an insn between
    FROM_INSN and TO_INSN (exclusive of those two).  */
@@ -1118,41 +949,6 @@
 
   return 0;
 }
-
-/* Return true if anything in insn X is (anti,output,true) dependent on
-   anything in insn Y.  */
-
-int
-insn_dependent_p (rtx x, rtx y)
-{
-  rtx tmp;
-
-  if (! INSN_P (x) || ! INSN_P (y))
-    abort ();
-
-  tmp = PATTERN (y);
-  note_stores (PATTERN (x), insn_dependent_p_1, &tmp);
-  if (tmp == NULL_RTX)
-    return 1;
-
-  tmp = PATTERN (x);
-  note_stores (PATTERN (y), insn_dependent_p_1, &tmp);
-  if (tmp == NULL_RTX)
-    return 1;
-
-  return 0;
-}
-
-/* A helper routine for insn_dependent_p called through note_stores.  */
-
-static void
-insn_dependent_p_1 (rtx x, rtx pat ATTRIBUTE_UNUSED, void *data)
-{
-  rtx * pinsn = (rtx *) data;
-
-  if (*pinsn && reg_mentioned_p (x, *pinsn))
-    *pinsn = NULL_RTX;
-}
 
 /* Helper function for set_of.  */
 struct set_of_data
@@ -1584,54 +1380,6 @@
   abort ();
 }
 
-/* Return the last value to which REG was set prior to INSN.  If we can't
-   find it easily, return 0.
-
-   We only return a REG, SUBREG, or constant because it is too hard to
-   check if a MEM remains unchanged.  */
-
-rtx
-reg_set_last (rtx x, rtx insn)
-{
-  rtx orig_insn = insn;
-
-  /* Scan backwards until reg_set_last_1 changed one of the above flags.
-     Stop when we reach a label or X is a hard reg and we reach a
-     CALL_INSN (if reg_set_last_last_regno is a hard reg).
-
-     If we find a set of X, ensure that its SET_SRC remains unchanged.  */
-
-  /* We compare with <= here, because reg_set_last_last_regno
-     is actually the number of the first reg *not* in X.  */
-  for (;
-       insn && GET_CODE (insn) != CODE_LABEL
-       && ! (GET_CODE (insn) == CALL_INSN
-	     && REGNO (x) <= FIRST_PSEUDO_REGISTER);
-       insn = PREV_INSN (insn))
-    if (INSN_P (insn))
-      {
-	rtx set = set_of (x, insn);
-	/* OK, this function modify our register.  See if we understand it.  */
-	if (set)
-	  {
-	    rtx last_value;
-	    if (GET_CODE (set) != SET || SET_DEST (set) != x)
-	      return 0;
-	    last_value = SET_SRC (x);
-	    if (CONSTANT_P (last_value)
-		|| ((GET_CODE (last_value) == REG
-		     || GET_CODE (last_value) == SUBREG)
-		    && ! reg_set_between_p (last_value,
-					    insn, orig_insn)))
-	      return last_value;
-	    else
-	      return 0;
-	  }
-      }
-
-  return 0;
-}
-
 /* Call FUN on each register or MEM that is stored into or clobbered by X.
    (X would be the pattern of an insn).
    FUN receives two arguments:
@@ -3453,259 +3201,4 @@
 	}
     }
   return false;
-}
-
-/* Return true when store to register X can be hoisted to the place
-   with LIVE registers (can be NULL).  Value VAL contains destination
-   whose value will be used.  */
-
-static bool
-hoist_test_store (rtx x, rtx val, regset live)
-{
-  if (GET_CODE (x) == SCRATCH)
-    return true;
-
-  if (rtx_equal_p (x, val))
-    return true;
-
-  /* Allow subreg of X in case it is not writing just part of multireg pseudo.
-     Then we would need to update all users to care hoisting the store too.
-     Caller may represent that by specifying whole subreg as val.  */
-
-  if (GET_CODE (x) == SUBREG && rtx_equal_p (SUBREG_REG (x), val))
-    {
-      if (GET_MODE_SIZE (GET_MODE (SUBREG_REG (x))) > UNITS_PER_WORD
-	  && GET_MODE_BITSIZE (GET_MODE (x)) <
-	  GET_MODE_BITSIZE (GET_MODE (SUBREG_REG (x))))
-	return false;
-      return true;
-    }
-  if (GET_CODE (x) == SUBREG)
-    x = SUBREG_REG (x);
-
-  /* Anything except register store is not hoistable.  This includes the
-     partial stores to registers.  */
-
-  if (!REG_P (x))
-    return false;
-
-  /* Pseudo registers can be always replaced by another pseudo to avoid
-     the side effect, for hard register we must ensure that they are dead.
-     Eventually we may want to add code to try turn pseudos to hards, but it
-     is unlikely useful.  */
-
-  if (REGNO (x) < FIRST_PSEUDO_REGISTER)
-    {
-      int regno = REGNO (x);
-      int n = HARD_REGNO_NREGS (regno, GET_MODE (x));
-
-      if (!live)
-	return false;
-      if (REGNO_REG_SET_P (live, regno))
-	return false;
-      while (--n > 0)
-	if (REGNO_REG_SET_P (live, regno + n))
-	  return false;
-    }
-  return true;
-}
-
-
-/* Return true if INSN can be hoisted to place with LIVE hard registers
-   (LIVE can be NULL when unknown).  VAL is expected to be stored by the insn
-   and used by the hoisting pass.  */
-
-bool
-can_hoist_insn_p (rtx insn, rtx val, regset live)
-{
-  rtx pat = PATTERN (insn);
-  int i;
-
-  /* It probably does not worth the complexity to handle multiple
-     set stores.  */
-  if (!single_set (insn))
-    return false;
-  /* We can move CALL_INSN, but we need to check that all caller clobbered
-     regs are dead.  */
-  if (GET_CODE (insn) == CALL_INSN)
-    return false;
-  /* In future we will handle hoisting of libcall sequences, but
-     give up for now.  */
-  if (find_reg_note (insn, REG_RETVAL, NULL_RTX))
-    return false;
-  switch (GET_CODE (pat))
-    {
-    case SET:
-      if (!hoist_test_store (SET_DEST (pat), val, live))
-	return false;
-      break;
-    case USE:
-      /* USES do have sick semantics, so do not move them.  */
-      return false;
-      break;
-    case CLOBBER:
-      if (!hoist_test_store (XEXP (pat, 0), val, live))
-	return false;
-      break;
-    case PARALLEL:
-      for (i = 0; i < XVECLEN (pat, 0); i++)
-	{
-	  rtx x = XVECEXP (pat, 0, i);
-	  switch (GET_CODE (x))
-	    {
-	    case SET:
-	      if (!hoist_test_store (SET_DEST (x), val, live))
-		return false;
-	      break;
-	    case USE:
-	      /* We need to fix callers to really ensure availability
-	         of all values insn uses, but for now it is safe to prohibit
-		 hoisting of any insn having such a hidden uses.  */
-	      return false;
-	      break;
-	    case CLOBBER:
-	      if (!hoist_test_store (SET_DEST (x), val, live))
-		return false;
-	      break;
-	    default:
-	      break;
-	    }
-	}
-      break;
-    default:
-      abort ();
-    }
-  return true;
-}
-
-/* Update store after hoisting - replace all stores to pseudo registers
-   by new ones to avoid clobbering of values except for store to VAL that will
-   be updated to NEW.  */
-
-static void
-hoist_update_store (rtx insn, rtx *xp, rtx val, rtx new)
-{
-  rtx x = *xp;
-
-  if (GET_CODE (x) == SCRATCH)
-    return;
-
-  if (GET_CODE (x) == SUBREG && SUBREG_REG (x) == val)
-    validate_change (insn, xp,
-		     simplify_gen_subreg (GET_MODE (x), new, GET_MODE (new),
-					  SUBREG_BYTE (x)), 1);
-  if (rtx_equal_p (x, val))
-    {
-      validate_change (insn, xp, new, 1);
-      return;
-    }
-  if (GET_CODE (x) == SUBREG)
-    {
-      xp = &SUBREG_REG (x);
-      x = *xp;
-    }
-
-  if (!REG_P (x))
-    abort ();
-
-  /* We've verified that hard registers are dead, so we may keep the side
-     effect.  Otherwise replace it by new pseudo.  */
-  if (REGNO (x) >= FIRST_PSEUDO_REGISTER)
-    validate_change (insn, xp, gen_reg_rtx (GET_MODE (x)), 1);
-  REG_NOTES (insn)
-    = alloc_EXPR_LIST (REG_UNUSED, *xp, REG_NOTES (insn));
-}
-
-/* Create a copy of INSN after AFTER replacing store of VAL to NEW
-   and each other side effect to pseudo register by new pseudo register.  */
-
-rtx
-hoist_insn_after (rtx insn, rtx after, rtx val, rtx new)
-{
-  rtx pat;
-  int i;
-  rtx note;
-
-  insn = emit_copy_of_insn_after (insn, after);
-  pat = PATTERN (insn);
-
-  /* Remove REG_UNUSED notes as we will re-emit them.  */
-  while ((note = find_reg_note (insn, REG_UNUSED, NULL_RTX)))
-    remove_note (insn, note);
-
-  /* To get this working callers must ensure to move everything referenced
-     by REG_EQUAL/REG_EQUIV notes too.  Lets remove them, it is probably
-     easier.  */
-  while ((note = find_reg_note (insn, REG_EQUAL, NULL_RTX)))
-    remove_note (insn, note);
-  while ((note = find_reg_note (insn, REG_EQUIV, NULL_RTX)))
-    remove_note (insn, note);
-
-  /* Remove REG_DEAD notes as they might not be valid anymore in case
-     we create redundancy.  */
-  while ((note = find_reg_note (insn, REG_DEAD, NULL_RTX)))
-    remove_note (insn, note);
-  switch (GET_CODE (pat))
-    {
-    case SET:
-      hoist_update_store (insn, &SET_DEST (pat), val, new);
-      break;
-    case USE:
-      break;
-    case CLOBBER:
-      hoist_update_store (insn, &XEXP (pat, 0), val, new);
-      break;
-    case PARALLEL:
-      for (i = 0; i < XVECLEN (pat, 0); i++)
-	{
-	  rtx x = XVECEXP (pat, 0, i);
-	  switch (GET_CODE (x))
-	    {
-	    case SET:
-	      hoist_update_store (insn, &SET_DEST (x), val, new);
-	      break;
-	    case USE:
-	      break;
-	    case CLOBBER:
-	      hoist_update_store (insn, &SET_DEST (x), val, new);
-	      break;
-	    default:
-	      break;
-	    }
-	}
-      break;
-    default:
-      abort ();
-    }
-  if (!apply_change_group ())
-    abort ();
-
-  return insn;
-}
-
-rtx
-hoist_insn_to_edge (rtx insn, edge e, rtx val, rtx new)
-{
-  rtx new_insn;
-
-  /* We cannot insert instructions on an abnormal critical edge.
-     It will be easier to find the culprit if we die now.  */
-  if ((e->flags & EDGE_ABNORMAL) && EDGE_CRITICAL_P (e))
-    abort ();
-
-  /* Do not use emit_insn_on_edge as we want to preserve notes and similar
-     stuff.  We also emit CALL_INSNS and firends.  */
-  if (e->insns == NULL_RTX)
-    {
-      start_sequence ();
-      emit_note (NOTE_INSN_DELETED);
-    }
-  else
-    push_to_sequence (e->insns);
-
-  new_insn = hoist_insn_after (insn, get_last_insn (), val, new);
-
-  e->insns = get_insns ();
-  end_sequence ();
-  return new_insn;
 }


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]