OSDN Git Service

(assign_parms): Don't trust the callee to copy a TREE_ADDRESSABLE
[pf3gnuchains/gcc-fork.git] / gcc / combine.c
index 49b3b80..323db6b 100644 (file)
@@ -1,5 +1,5 @@
 /* Optimize by combining instructions for GNU compiler.
-   Copyright (C) 1987, 1988, 1992, 1993, 1994 Free Software Foundation, Inc.
+   Copyright (C) 1987, 88, 92, 93, 94, 1995 Free Software Foundation, Inc.
 
 This file is part of GNU CC.
 
@@ -15,7 +15,8 @@ GNU General Public License for more details.
 
 You should have received a copy of the GNU General Public License
 along with GNU CC; see the file COPYING.  If not, write to
-the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
+the Free Software Foundation, 59 Temple Place - Suite 330,
+Boston, MA 02111-1307, USA.  */
 
 
 /* This module is essentially the "combiner" phase of the U. of Arizona
@@ -75,9 +76,9 @@ the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
 
 #include "config.h"
 #ifdef __STDC__
-#include "gstdarg.h"
+#include <stdarg.h>
 #else
-#include "gvarargs.h"
+#include <varargs.h>
 #endif
 
 /* Must precede rtl.h for FFS.  */
@@ -120,7 +121,7 @@ static int combine_successes;
 
 static int total_attempts, total_merges, total_extras, total_successes;
 
-/* Define a defulat value for REVERSIBLE_CC_MODE.
+/* Define a default value for REVERSIBLE_CC_MODE.
    We can never assume that a condition code mode is safe to reverse unless
    the md tells us so.  */
 #ifndef REVERSIBLE_CC_MODE
@@ -135,10 +136,13 @@ static int total_attempts, total_merges, total_extras, total_successes;
    the dumps produced by earlier passes with those from later passes.  */
 
 static int *uid_cuid;
+static int max_uid_cuid;
 
 /* Get the cuid of an insn.  */
 
-#define INSN_CUID(INSN) (uid_cuid[INSN_UID (INSN)])
+#define INSN_CUID(INSN) (INSN_UID (INSN) > max_uid_cuid                \
+                        ? (abort(), 0)                         \
+                        : uid_cuid[INSN_UID (INSN)])
 
 /* Maximum register number, which is the size of the tables below.  */
 
@@ -170,8 +174,8 @@ static int last_call_cuid;
 
 static rtx subst_insn;
 
-/* If nonzero, this is the insn that should be presumed to be
-   immediately in front of `subst_insn'.  */
+/* This is an insn that belongs before subst_insn, but is not currently
+   on the insn chain.  */
 
 static rtx subst_prev_insn;
 
@@ -399,6 +403,7 @@ static rtx expand_compound_operation  PROTO((rtx));
 static rtx expand_field_assignment  PROTO((rtx));
 static rtx make_extraction     PROTO((enum machine_mode, rtx, int, rtx, int,
                                       int, int, int));
+static rtx extract_left_shift  PROTO((rtx, int));
 static rtx make_compound_operation  PROTO((rtx, enum rtx_code));
 static int get_pos_from_mask   PROTO((unsigned HOST_WIDE_INT, int *));
 static rtx force_to_mode       PROTO((rtx, enum machine_mode,
@@ -416,13 +421,14 @@ static int merge_outer_ops        PROTO((enum rtx_code *, HOST_WIDE_INT *,
                                       enum machine_mode, int *));
 static rtx simplify_shift_const        PROTO((rtx, enum rtx_code, enum machine_mode,
                                       rtx, int));
-static int recog_for_combine   PROTO((rtx *, rtx, rtx *));
+static int recog_for_combine   PROTO((rtx *, rtx, rtx *, int *));
 static rtx gen_lowpart_for_combine  PROTO((enum machine_mode, rtx));
 static rtx gen_rtx_combine PVPROTO((enum rtx_code code, enum machine_mode mode,
                                  ...));
 static rtx gen_binary          PROTO((enum rtx_code, enum machine_mode,
                                       rtx, rtx));
-static rtx gen_unary           PROTO((enum rtx_code, enum machine_mode, rtx));
+static rtx gen_unary           PROTO((enum rtx_code, enum machine_mode,
+                                      enum machine_mode, rtx));
 static enum rtx_code simplify_comparison  PROTO((enum rtx_code, rtx *, rtx *));
 static int reversible_comparison_p  PROTO((rtx));
 static void update_table_tick  PROTO((rtx));
@@ -464,7 +470,7 @@ combine_instructions (f, nregs)
     = (unsigned HOST_WIDE_INT *) alloca (nregs * sizeof (HOST_WIDE_INT));
   reg_sign_bit_copies = (char *) alloca (nregs * sizeof (char));
 
-  bzero (reg_nonzero_bits, nregs * sizeof (HOST_WIDE_INT));
+  bzero ((char *) reg_nonzero_bits, nregs * sizeof (HOST_WIDE_INT));
   bzero (reg_sign_bit_copies, nregs * sizeof (char));
 
   reg_last_death = (rtx *) alloca (nregs * sizeof (rtx));
@@ -491,6 +497,7 @@ combine_instructions (f, nregs)
       i = INSN_UID (insn);
 
   uid_cuid = (int *) alloca ((i + 1) * sizeof (int));
+  max_uid_cuid = i;
 
   nonzero_bits_mode = mode_for_size (HOST_BITS_PER_WIDE_INT, MODE_INT, 0);
 
@@ -512,11 +519,15 @@ combine_instructions (f, nregs)
 
   label_tick = 1;
 
+  /* We need to initialize it here, because record_dead_and_set_regs may call
+     get_last_value.  */
+  subst_prev_insn = NULL_RTX;
+
   setup_incoming_promotions ();
 
   for (insn = f, i = 0; insn; insn = NEXT_INSN (insn))
     {
-      INSN_CUID (insn) = ++i;
+      uid_cuid[INSN_UID (insn)] = ++i;
       subst_low_cuid = i;
       subst_insn = insn;
 
@@ -657,14 +668,14 @@ init_reg_last_arrays ()
 {
   int nregs = combine_max_regno;
 
-  bzero (reg_last_death, nregs * sizeof (rtx));
-  bzero (reg_last_set, nregs * sizeof (rtx));
-  bzero (reg_last_set_value, nregs * sizeof (rtx));
-  bzero (reg_last_set_table_tick, nregs * sizeof (int));
-  bzero (reg_last_set_label, nregs * sizeof (int));
+  bzero ((char *) reg_last_death, nregs * sizeof (rtx));
+  bzero ((char *) reg_last_set, nregs * sizeof (rtx));
+  bzero ((char *) reg_last_set_value, nregs * sizeof (rtx));
+  bzero ((char *) reg_last_set_table_tick, nregs * sizeof (int));
+  bzero ((char *) reg_last_set_label, nregs * sizeof (int));
   bzero (reg_last_set_invalid, nregs * sizeof (char));
-  bzero (reg_last_set_mode, nregs * sizeof (enum machine_mode));
-  bzero (reg_last_set_nonzero_bits, nregs * sizeof (HOST_WIDE_INT));
+  bzero ((char *) reg_last_set_mode, nregs * sizeof (enum machine_mode));
+  bzero ((char *) reg_last_set_nonzero_bits, nregs * sizeof (HOST_WIDE_INT));
   bzero (reg_last_set_sign_bit_copies, nregs * sizeof (char));
 }
 \f
@@ -877,6 +888,12 @@ can_combine_p (insn, i3, pred, succ, pdest, psrc)
       || (rtx_equal_p (src, dest) && find_reg_note (insn, REG_EQUAL, NULL_RTX))
       /* Can't merge a function call.  */
       || GET_CODE (src) == CALL
+      /* Don't eliminate a function call argument.  */
+      || (GET_CODE (i3) == CALL_INSN
+         && (find_reg_fusage (i3, USE, dest)
+             || (GET_CODE (dest) == REG
+                 && REGNO (dest) < FIRST_PSEUDO_REGISTER
+                 && global_regs[REGNO (dest)])))
       /* Don't substitute into an incremented register.  */
       || FIND_REG_INC_NOTE (i3, dest)
       || (succ && FIND_REG_INC_NOTE (succ, dest))
@@ -927,14 +944,16 @@ can_combine_p (insn, i3, pred, succ, pdest, psrc)
       if (GET_CODE (src) == REG
          && ((REGNO (dest) < FIRST_PSEUDO_REGISTER
               && ! HARD_REGNO_MODE_OK (REGNO (dest), GET_MODE (dest)))
-#ifdef SMALL_REGISTER_CLASSES
-             /* Don't extend the life of a hard register.  */
-             || REGNO (src) < FIRST_PSEUDO_REGISTER
-#else
+             /* Don't extend the life of a hard register unless it is
+                user variable (if we have few registers) or it can't
+                fit into the desired register (meaning something special
+                is going on).  */
              || (REGNO (src) < FIRST_PSEUDO_REGISTER
-                 && ! HARD_REGNO_MODE_OK (REGNO (src), GET_MODE (src)))
+                 && (! HARD_REGNO_MODE_OK (REGNO (src), GET_MODE (src))
+#ifdef SMALL_REGISTER_CLASSES
+                     || ! REG_USERVAR_P (src)
 #endif
-         ))
+                     ))))
        return 0;
     }
   else if (GET_CODE (dest) != CC0)
@@ -1038,7 +1057,8 @@ can_combine_p (insn, i3, pred, succ, pdest, psrc)
    of a SET must prevent combination from occurring.
 
    On machines where SMALL_REGISTER_CLASSES is defined, we don't combine
-   if the destination of a SET is a hard register.
+   if the destination of a SET is a hard register that isn't a user
+   variable.
 
    Before doing the above check, we first try to expand a field assignment
    into a set of logical operations.
@@ -1108,14 +1128,12 @@ combinable_i3pat (i3, loc, i2dest, i1dest, i1_not_in_src, pi3dest_killed)
             CALL operation.  */
          || (GET_CODE (inner_dest) == REG
              && REGNO (inner_dest) < FIRST_PSEUDO_REGISTER
+             && (! HARD_REGNO_MODE_OK (REGNO (inner_dest),
+                                       GET_MODE (inner_dest))
 #ifdef SMALL_REGISTER_CLASSES
-             && GET_CODE (src) != CALL
-#else
-             && ! HARD_REGNO_MODE_OK (REGNO (inner_dest),
-                                      GET_MODE (inner_dest))
+                || (GET_CODE (src) != CALL && ! REG_USERVAR_P (inner_dest))
 #endif
-             )
-
+                 ))
          || (i1_not_in_src && reg_overlap_mentioned_p (i1dest, src)))
        return 0;
 
@@ -1198,6 +1216,10 @@ try_combine (i3, i2, i1)
   rtx new_i3_notes, new_i2_notes;
   /* Notes that we substituted I3 into I2 instead of the normal case.  */
   int i3_subst_into_i2 = 0;
+  /* Notes that I1, I2 or I3 is a MULT operation.  */
+  int have_mult = 0;
+  /* Number of clobbers of SCRATCH we had to add.  */
+  int i3_scratches = 0, i2_scratches = 0, other_scratches = 0;
 
   int maxreg;
   rtx temp;
@@ -1233,7 +1255,6 @@ try_combine (i3, i2, i1)
   if (i1 && INSN_CUID (i1) > INSN_CUID (i2))
     temp = i1, i1 = i2, i2 = temp;
 
-  subst_prev_insn = 0;
   added_links_insn = 0;
 
   /* First check for one important special-case that the code below will
@@ -1254,7 +1275,8 @@ try_combine (i3, i2, i1)
       && REGNO (SET_SRC (PATTERN (i3))) >= FIRST_PSEUDO_REGISTER
 #ifdef SMALL_REGISTER_CLASSES
       && (GET_CODE (SET_DEST (PATTERN (i3))) != REG
-         || REGNO (SET_DEST (PATTERN (i3))) >= FIRST_PSEUDO_REGISTER)
+         || REGNO (SET_DEST (PATTERN (i3))) >= FIRST_PSEUDO_REGISTER
+         || REG_USERVAR_P (SET_DEST (PATTERN (i3))))
 #endif
       && find_reg_note (i3, REG_DEAD, SET_SRC (PATTERN (i3)))
       && GET_CODE (PATTERN (i2)) == PARALLEL
@@ -1386,6 +1408,15 @@ try_combine (i3, i2, i1)
       return 0;
     }
 
+  /* See if any of the insns is a MULT operation.  Unless one is, we will
+     reject a combination that is, since it must be slower.  Be conservative
+     here.  */
+  if (GET_CODE (i2src) == MULT
+      || (i1 != 0 && GET_CODE (i1src) == MULT)
+      || (GET_CODE (PATTERN (i3)) == SET
+         && GET_CODE (SET_SRC (PATTERN (i3))) == MULT))
+    have_mult = 1;
+
   /* If I3 has an inc, then give up if I1 or I2 uses the reg that is inc'd.
      We used to do this EXCEPT in one case: I3 has a post-inc in an
      output operand.  However, that exception can give rise to insns like
@@ -1595,7 +1626,11 @@ try_combine (i3, i2, i1)
         really no reason to).  */
       || max_reg_num () != maxreg
       /* Fail if we couldn't do something and have a CLOBBER.  */
-      || GET_CODE (newpat) == CLOBBER)
+      || GET_CODE (newpat) == CLOBBER
+      /* Fail if this new pattern is a MULT and we didn't have one before
+        at the outer level.  */
+      || (GET_CODE (newpat) == SET && GET_CODE (SET_SRC (newpat)) == MULT
+         && ! have_mult))
     {
       undo_all ();
       return 0;
@@ -1615,7 +1650,7 @@ try_combine (i3, i2, i1)
          rtvec old = XVEC (newpat, 0);
          total_sets = XVECLEN (newpat, 0) + added_sets_1 + added_sets_2;
          newpat = gen_rtx (PARALLEL, VOIDmode, rtvec_alloc (total_sets));
-         bcopy (&old->elem[0], &XVECEXP (newpat, 0, 0),
+         bcopy ((char *) &old->elem[0], (char *) &XVECEXP (newpat, 0, 0),
                 sizeof (old->elem[0]) * old->num_elem);
        }
       else
@@ -1653,7 +1688,8 @@ try_combine (i3, i2, i1)
   mark_used_regs_combine (newpat);
 
   /* Is the result of combination a valid instruction?  */
-  insn_code_number = recog_for_combine (&newpat, i3, &new_i3_notes);
+  insn_code_number
+    = recog_for_combine (&newpat, i3, &new_i3_notes, &i3_scratches);
 
   /* If the result isn't valid, see if it is a PARALLEL of two SETs where
      the second SET's destination is a register that is unused.  In that case,
@@ -1674,7 +1710,8 @@ try_combine (i3, i2, i1)
       && asm_noperands (newpat) < 0)
     {
       newpat = XVECEXP (newpat, 0, 0);
-      insn_code_number = recog_for_combine (&newpat, i3, &new_i3_notes);
+      insn_code_number
+       = recog_for_combine (&newpat, i3, &new_i3_notes, &i3_scratches);
     }
 
   else if (insn_code_number < 0 && GET_CODE (newpat) == PARALLEL
@@ -1687,35 +1724,10 @@ try_combine (i3, i2, i1)
           && asm_noperands (newpat) < 0)
     {
       newpat = XVECEXP (newpat, 0, 1);
-      insn_code_number = recog_for_combine (&newpat, i3, &new_i3_notes);
+      insn_code_number
+       = recog_for_combine (&newpat, i3, &new_i3_notes, &i3_scratches);
     }
 
-  /* See if this is an XOR.  If so, perhaps the problem is that the
-     constant is out of range.  Replace it with a complemented XOR with
-     a complemented constant; it might be in range.  */
-
-  else if (insn_code_number < 0 && GET_CODE (newpat) == SET
-          && GET_CODE (SET_SRC (newpat)) == XOR
-          && GET_CODE (XEXP (SET_SRC (newpat), 1)) == CONST_INT
-          && ((temp = simplify_unary_operation (NOT,
-                                                GET_MODE (SET_SRC (newpat)),
-                                                XEXP (SET_SRC (newpat), 1),
-                                                GET_MODE (SET_SRC (newpat))))
-              != 0))
-    {
-      enum machine_mode i_mode = GET_MODE (SET_SRC (newpat));
-      rtx pat
-       = gen_rtx_combine (SET, VOIDmode, SET_DEST (newpat),
-                          gen_unary (NOT, i_mode,
-                                     gen_binary (XOR, i_mode,
-                                                 XEXP (SET_SRC (newpat), 0),
-                                                 temp)));
-
-      insn_code_number = recog_for_combine (&pat, i3, &new_i3_notes);
-      if (insn_code_number >= 0)
-       newpat = pat;
-    }
-                                                       
   /* If we were combining three insns and the result is a simple SET
      with no ASM_OPERANDS that wasn't recognized, try to split it into two
      insns.  There are two ways to do this.  It can be split using a 
@@ -1782,15 +1794,15 @@ try_combine (i3, i2, i1)
          if (REGNO (i2dest) >= FIRST_PSEUDO_REGISTER)
            SUBST (regno_reg_rtx[REGNO (i2dest)], ni2dest);
 
-         i2_code_number = recog_for_combine (&newi2pat, i2, &new_i2_notes);
+         i2_code_number = recog_for_combine (&newi2pat, i2, &new_i2_notes,
+                                             &i2_scratches);
 
          /* If I2 or I3 has multiple SETs, we won't know how to track
             register status, so don't use these insns.  */
 
          if (i2_code_number >= 0 && i2set && i3set)
-           insn_code_number = recog_for_combine (&newi3pat, i3,
-                                                 &new_i3_notes);
-
+           insn_code_number = recog_for_combine (&newi3pat, i3, &new_i3_notes,
+                                                 &i3_scratches); 
          if (insn_code_number >= 0)
            newpat = newi3pat;
 
@@ -1824,13 +1836,14 @@ try_combine (i3, i2, i1)
          && ! reg_referenced_p (i2dest, newpat))
        {
          rtx newdest = i2dest;
+         enum rtx_code split_code = GET_CODE (*split);
+         enum machine_mode split_mode = GET_MODE (*split);
 
          /* Get NEWDEST as a register in the proper mode.  We have already
             validated that we can do this.  */
-         if (GET_MODE (i2dest) != GET_MODE (*split)
-             && GET_MODE (*split) != VOIDmode)
+         if (GET_MODE (i2dest) != split_mode && split_mode != VOIDmode)
            {
-             newdest = gen_rtx (REG, GET_MODE (*split), REGNO (i2dest));
+             newdest = gen_rtx (REG, split_mode, REGNO (i2dest));
 
              if (REGNO (i2dest) >= FIRST_PSEUDO_REGISTER)
                SUBST (regno_reg_rtx[REGNO (i2dest)], newdest);
@@ -1839,26 +1852,35 @@ try_combine (i3, i2, i1)
          /* If *SPLIT is a (mult FOO (const_int pow2)), convert it to
             an ASHIFT.  This can occur if it was inside a PLUS and hence
             appeared to be a memory address.  This is a kludge.  */
-         if (GET_CODE (*split) == MULT
+         if (split_code == MULT
              && GET_CODE (XEXP (*split, 1)) == CONST_INT
              && (i = exact_log2 (INTVAL (XEXP (*split, 1)))) >= 0)
-           SUBST (*split, gen_rtx_combine (ASHIFT, GET_MODE (*split),
-                                           XEXP (*split, 0), GEN_INT (i)));
+           {
+             SUBST (*split, gen_rtx_combine (ASHIFT, split_mode,
+                                             XEXP (*split, 0), GEN_INT (i)));
+             /* Update split_code because we may not have a multiply
+                anymore.  */
+             split_code = GET_CODE (*split);
+           }
 
 #ifdef INSN_SCHEDULING
          /* If *SPLIT is a paradoxical SUBREG, when we split it, it should
             be written as a ZERO_EXTEND.  */
-         if (GET_CODE (*split) == SUBREG
-             && GET_CODE (SUBREG_REG (*split)) == MEM)
-           SUBST (*split, gen_rtx_combine (ZERO_EXTEND, GET_MODE (*split),
+         if (split_code == SUBREG && GET_CODE (SUBREG_REG (*split)) == MEM)
+           SUBST (*split, gen_rtx_combine (ZERO_EXTEND, split_mode,
                                            XEXP (*split, 0)));
 #endif
 
          newi2pat = gen_rtx_combine (SET, VOIDmode, newdest, *split);
          SUBST (*split, newdest);
-         i2_code_number = recog_for_combine (&newi2pat, i2, &new_i2_notes);
-         if (i2_code_number >= 0)
-           insn_code_number = recog_for_combine (&newpat, i3, &new_i3_notes);
+         i2_code_number
+           = recog_for_combine (&newi2pat, i2, &new_i2_notes, &i2_scratches);
+
+         /* If the split point was a MULT and we didn't have one before,
+            don't use one now.  */
+         if (i2_code_number >= 0 && ! (split_code == MULT && ! have_mult))
+           insn_code_number
+             = recog_for_combine (&newpat, i3, &new_i3_notes, &i3_scratches);
        }
     }
 
@@ -1912,9 +1934,12 @@ try_combine (i3, i2, i1)
       newpat = XVECEXP (newpat, 0, 1);
       SUBST (SET_SRC (newpat),
             gen_lowpart_for_combine (GET_MODE (SET_SRC (newpat)), ni2dest));
-      i2_code_number = recog_for_combine (&newi2pat, i2, &new_i2_notes);
+      i2_code_number
+       = recog_for_combine (&newi2pat, i2, &new_i2_notes, &i2_scratches);
+
       if (i2_code_number >= 0)
-       insn_code_number = recog_for_combine (&newpat, i3, &new_i3_notes);
+       insn_code_number
+         = recog_for_combine (&newpat, i3, &new_i3_notes, &i3_scratches);
 
       if (insn_code_number >= 0)
        {
@@ -1988,9 +2013,12 @@ try_combine (i3, i2, i1)
       newi2pat = XVECEXP (newpat, 0, 1);
       newpat = XVECEXP (newpat, 0, 0);
 
-      i2_code_number = recog_for_combine (&newi2pat, i2, &new_i2_notes);
+      i2_code_number
+       = recog_for_combine (&newi2pat, i2, &new_i2_notes, &i2_scratches);
+
       if (i2_code_number >= 0)
-       insn_code_number = recog_for_combine (&newpat, i3, &new_i3_notes);
+       insn_code_number
+         = recog_for_combine (&newpat, i3, &new_i3_notes, &i3_scratches);
     }
 
   /* If it still isn't recognized, fail and change things back the way they
@@ -2012,8 +2040,9 @@ try_combine (i3, i2, i1)
 
       CLEAR_HARD_REG_SET (newpat_used_regs);
 
-      other_code_number = recog_for_combine (&other_pat, undobuf.other_insn,
-                                            &new_other_notes);
+      other_code_number
+       = recog_for_combine (&other_pat, undobuf.other_insn,
+                            &new_other_notes, &other_scratches);
 
       if (other_code_number < 0 && ! check_asm_operands (other_pat))
        {
@@ -2274,7 +2303,7 @@ try_combine (i3, i2, i1)
 
        /* If the reg formerly set in I2 died only once and that was in I3,
           zero its use count so it won't make `reload' do any work.  */
-       if (! added_sets_2 && newi2pat == 0)
+       if (! added_sets_2 && newi2pat == 0 && ! i2dest_in_i2src)
          {
            regno = REGNO (i2dest);
            reg_n_sets[regno]--;
@@ -2298,7 +2327,7 @@ try_combine (i3, i2, i1)
        record_value_for_reg (i1dest, i1_insn, i1_val);
 
        regno = REGNO (i1dest);
-       if (! added_sets_1)
+       if (! added_sets_1 && ! i1dest_in_i1src)
          {
            reg_n_sets[regno]--;
            if (reg_n_sets[regno] == 0
@@ -2315,6 +2344,12 @@ try_combine (i3, i2, i1)
     if (newi2pat)
       note_stores (newi2pat, set_nonzero_bits_and_sign_copies);
 
+    /* If we added any (clobber (scratch)), add them to the max for a
+       block.  This is a very pessimistic calculation, since we might
+       have had them already and this might not be the worst block, but
+       it's not worth doing any better.  */
+    max_scratch += i3_scratches + i2_scratches + other_scratches;
+
     /* If I3 is now an unconditional jump, ensure that it has a 
        BARRIER following it since it may have initially been a
        conditional jump.  It may also be the last nonnote insn.  */
@@ -2327,6 +2362,10 @@ try_combine (i3, i2, i1)
 
   combine_successes++;
 
+  /* Clear this here, so that subsequent get_last_value calls are not
+     affected.  */
+  subst_prev_insn = NULL_RTX;
+
   if (added_links_insn
       && (newi2pat == 0 || INSN_CUID (added_links_insn) < INSN_CUID (i2))
       && INSN_CUID (added_links_insn) < INSN_CUID (i3))
@@ -2354,6 +2393,10 @@ undo_all ()
 
   obfree (undobuf.storage);
   undobuf.num_undo = 0;
+
+  /* Clear this here, so that subsequent get_last_value calls are not
+     affected.  */
+  subst_prev_insn = NULL_RTX;
 }
 \f
 /* Find the innermost point within the rtx at LOC, possibly LOC itself,
@@ -2404,7 +2447,7 @@ find_split_point (loc, insn)
       /* If we have a PLUS whose second operand is a constant and the
         address is not valid, perhaps will can split it up using
         the machine-specific way to split large constants.  We use
-        the first psuedo-reg (one of the virtual regs) as a placeholder;
+        the first pseudo-reg (one of the virtual regs) as a placeholder;
         it will not remain in the result.  */
       if (GET_CODE (XEXP (x, 0)) == PLUS
          && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT
@@ -2508,9 +2551,8 @@ find_split_point (loc, insn)
          enum machine_mode mode = GET_MODE (dest);
          unsigned HOST_WIDE_INT mask = ((HOST_WIDE_INT) 1 << len) - 1;
 
-#if BITS_BIG_ENDIAN
-         pos = GET_MODE_BITSIZE (mode) - len - pos;
-#endif
+         if (BITS_BIG_ENDIAN)
+           pos = GET_MODE_BITSIZE (mode) - len - pos;
 
          if (src == mask)
            SUBST (SET_SRC (x),
@@ -2579,9 +2621,8 @@ find_split_point (loc, insn)
              len = INTVAL (XEXP (SET_SRC (x), 1));
              pos = INTVAL (XEXP (SET_SRC (x), 2));
 
-#if BITS_BIG_ENDIAN
-             pos = GET_MODE_BITSIZE (GET_MODE (inner)) - len - pos;
-#endif
+             if (BITS_BIG_ENDIAN)
+               pos = GET_MODE_BITSIZE (GET_MODE (inner)) - len - pos;
              unsignedp = (code == ZERO_EXTRACT);
            }
          break;
@@ -3016,6 +3057,9 @@ simplify_rtx (x, op0_mode, last, in_dest)
          rtx cop1 = const0_rtx;
          enum rtx_code cond_code = simplify_comparison (NE, &cond, &cop1);
 
+         if (cond_code == NE && GET_RTX_CLASS (GET_CODE (cond)) == '<')
+           return x;
+
          /* Simplify the alternative arms; this may collapse the true and 
             false arms to store-flag values.  */
          true = subst (true, pc_rtx, pc_rtx, 0, 0);
@@ -3036,12 +3080,12 @@ simplify_rtx (x, op0_mode, last, in_dest)
          else if (GET_CODE (true) == CONST_INT
                   && INTVAL (true) == - STORE_FLAG_VALUE
                   && false == const0_rtx)
-           x = gen_unary (NEG, mode,
+           x = gen_unary (NEG, mode, mode,
                           gen_binary (cond_code, mode, cond, cop1));
          else if (GET_CODE (false) == CONST_INT
                   && INTVAL (false) == - STORE_FLAG_VALUE
                   && true == const0_rtx)
-           x = gen_unary (NEG, mode,
+           x = gen_unary (NEG, mode, mode,
                           gen_binary (reverse_condition (cond_code), 
                                       mode, cond, cop1));
          else
@@ -3165,12 +3209,14 @@ simplify_rtx (x, op0_mode, last, in_dest)
              || mode_dependent_address_p (XEXP (inner, 0)))
            return gen_rtx (CLOBBER, mode, const0_rtx);
 
-#if BYTES_BIG_ENDIAN
-         if (GET_MODE_SIZE (mode) < UNITS_PER_WORD)
-           endian_offset += UNITS_PER_WORD - GET_MODE_SIZE (mode);
-         if (GET_MODE_SIZE (GET_MODE (inner)) < UNITS_PER_WORD)
-           endian_offset -= UNITS_PER_WORD - GET_MODE_SIZE (GET_MODE (inner));
-#endif
+         if (BYTES_BIG_ENDIAN)
+           {
+             if (GET_MODE_SIZE (mode) < UNITS_PER_WORD)
+               endian_offset += UNITS_PER_WORD - GET_MODE_SIZE (mode);
+             if (GET_MODE_SIZE (GET_MODE (inner)) < UNITS_PER_WORD)
+               endian_offset -= (UNITS_PER_WORD
+                                 - GET_MODE_SIZE (GET_MODE (inner)));
+           }
          /* Note if the plus_constant doesn't make a valid address
             then this combination won't be accepted.  */
          x = gen_rtx (MEM, mode,
@@ -3246,10 +3292,8 @@ simplify_rtx (x, op0_mode, last, in_dest)
         only if the constant's mode fits in one word.  */
       if (CONSTANT_P (SUBREG_REG (x)) && subreg_lowpart_p (x)
          && GET_MODE_SIZE (mode) < GET_MODE_SIZE (op0_mode)
-#if WORDS_BIG_ENDIAN
-         && GET_MODE_BITSIZE (op0_mode) <= BITS_PER_WORD
-#endif
-         )
+         && (! WORDS_BIG_ENDIAN
+             || GET_MODE_BITSIZE (op0_mode) <= BITS_PER_WORD))
        return gen_lowpart_for_combine (mode, SUBREG_REG (x));
 
       /* A paradoxical SUBREG of a VOIDmode constant is the same constant,
@@ -3258,16 +3302,10 @@ simplify_rtx (x, op0_mode, last, in_dest)
          && GET_MODE_SIZE (mode) > GET_MODE_SIZE (op0_mode))
        return SUBREG_REG (x);
 
-      /* If we are narrowing an integral object, we need to see if we can
-        simplify the expression for the object knowing that we only need the
-        low-order bits.  */
+      /* Note that we cannot do any narrowing for non-constants since
+        we might have been counting on using the fact that some bits were
+        zero.  We now do this in the SET.  */
 
-      if (GET_MODE_CLASS (mode) == MODE_INT
-         && GET_MODE_CLASS (GET_MODE (SUBREG_REG (x))) == MODE_INT
-         && GET_MODE_SIZE (mode) < GET_MODE_SIZE (GET_MODE (SUBREG_REG (x)))
-         && subreg_lowpart_p (x))
-       return force_to_mode (SUBREG_REG (x), mode, GET_MODE_MASK (mode),
-                             NULL_RTX, 0);
       break;
 
     case NOT:
@@ -3287,10 +3325,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
          && (temp = simplify_unary_operation (NOT, mode,
                                               XEXP (XEXP (x, 0), 1),
                                               mode)) != 0)
-       {
-         SUBST (XEXP (XEXP (x, 0), 1), temp);
-         return XEXP (x, 0);
-       }
+       return gen_binary (XOR, mode, XEXP (XEXP (x, 0), 0), temp);
              
       /* (not (ashift 1 X)) is (rotate ~1 X).  We used to do this for operands
         other than 1, but that is not valid.  We could do a similar
@@ -3298,7 +3333,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
         but this doesn't seem common enough to bother with.  */
       if (GET_CODE (XEXP (x, 0)) == ASHIFT
          && XEXP (XEXP (x, 0), 0) == const1_rtx)
-       return gen_rtx (ROTATE, mode, gen_unary (NOT, mode, const1_rtx),
+       return gen_rtx (ROTATE, mode, gen_unary (NOT, mode, mode, const1_rtx),
                        XEXP (XEXP (x, 0), 1));
                                            
       if (GET_CODE (XEXP (x, 0)) == SUBREG
@@ -3311,7 +3346,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
          enum machine_mode inner_mode = GET_MODE (SUBREG_REG (XEXP (x, 0)));
 
          x = gen_rtx (ROTATE, inner_mode,
-                      gen_unary (NOT, inner_mode, const1_rtx),
+                      gen_unary (NOT, inner_mode, inner_mode, const1_rtx),
                       XEXP (SUBREG_REG (XEXP (x, 0)), 1));
          return gen_lowpart_for_combine (mode, x);
        }
@@ -3448,6 +3483,13 @@ simplify_rtx (x, op0_mode, last, in_dest)
        }
       break;
 
+    case TRUNCATE:
+      if (GET_MODE_BITSIZE (mode) <= HOST_BITS_PER_WIDE_INT)
+       SUBST (XEXP (x, 0),
+              force_to_mode (XEXP (x, 0), GET_MODE (XEXP (x, 0)),
+                             GET_MODE_MASK (mode), NULL_RTX, 0));
+      break;
+
     case FLOAT_TRUNCATE:
       /* (float_truncate:SF (float_extend:DF foo:SF)) = foo:SF.  */
       if (GET_CODE (XEXP (x, 0)) == FLOAT_EXTEND
@@ -3460,8 +3502,15 @@ simplify_rtx (x, op0_mode, last, in_dest)
           || GET_CODE (XEXP (x, 0)) == NEG)
          && GET_CODE (XEXP (XEXP (x, 0), 0)) == FLOAT_EXTEND
          && GET_MODE (XEXP (XEXP (XEXP (x, 0), 0), 0)) == mode)
-       return gen_unary (GET_CODE (XEXP (x, 0)),
-                         mode, XEXP (XEXP (XEXP (x, 0), 0), 0));
+       return gen_unary (GET_CODE (XEXP (x, 0)), mode, mode,
+                         XEXP (XEXP (XEXP (x, 0), 0), 0));
+
+      /* (float_truncate:SF (subreg:DF (float_truncate:SF X) 0))
+        is (float_truncate:SF x).  */
+      if (GET_CODE (XEXP (x, 0)) == SUBREG
+         && subreg_lowpart_p (XEXP (x, 0))
+         && GET_CODE (SUBREG_REG (XEXP (x, 0))) == FLOAT_TRUNCATE)
+       return SUBREG_REG (XEXP (x, 0));
       break;  
 
 #ifdef HAVE_cc0
@@ -3545,7 +3594,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
          && ((STORE_FLAG_VALUE == -1 && XEXP (x, 1) == const1_rtx)
              || (STORE_FLAG_VALUE == 1 && XEXP (x, 1) == constm1_rtx)))
        return
-         gen_unary (NEG, mode,
+         gen_unary (NEG, mode, mode,
                     gen_binary (reverse_condition (GET_CODE (XEXP (x, 0))),
                                 mode, XEXP (XEXP (x, 0), 0),
                                 XEXP (XEXP (x, 0), 1)));
@@ -3624,24 +3673,6 @@ simplify_rtx (x, op0_mode, last, in_dest)
          if (GET_CODE (x) != MULT)
            return x;
        }
-
-      /* If this is multiplication by a power of two and its first operand is
-        a shift, treat the multiply as a shift to allow the shifts to
-        possibly combine.  */
-      if (GET_CODE (XEXP (x, 1)) == CONST_INT
-         && (i = exact_log2 (INTVAL (XEXP (x, 1)))) >= 0
-         && (GET_CODE (XEXP (x, 0)) == ASHIFT
-             || GET_CODE (XEXP (x, 0)) == LSHIFTRT
-             || GET_CODE (XEXP (x, 0)) == ASHIFTRT
-             || GET_CODE (XEXP (x, 0)) == ROTATE
-             || GET_CODE (XEXP (x, 0)) == ROTATERT))
-       return simplify_shift_const (NULL_RTX, ASHIFT, mode, XEXP (x, 0), i);
-
-      /* Convert (mult (ashift (const_int 1) A) B) to (ashift B A).  */
-      if (GET_CODE (XEXP (x, 0)) == ASHIFT
-         && XEXP (XEXP (x, 0), 0) == const1_rtx)
-       return gen_rtx_combine (ASHIFT, mode, XEXP (x, 1),
-                               XEXP (XEXP (x, 0), 1));
       break;
 
     case UDIV:
@@ -3704,7 +3735,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
                       == GET_MODE_BITSIZE (mode)))
            {
              op0 = expand_compound_operation (op0);
-             return gen_unary (NEG, mode,
+             return gen_unary (NEG, mode, mode,
                                gen_lowpart_for_combine (mode, op0));
            }
 
@@ -3743,7 +3774,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
                   && nonzero_bits (op0, mode) == 1)
            {
              op0 = expand_compound_operation (op0);
-             return gen_unary (NEG, mode,
+             return gen_unary (NEG, mode, mode,
                                gen_lowpart_for_combine (mode, op0));
            }
 
@@ -3753,7 +3784,7 @@ simplify_rtx (x, op0_mode, last, in_dest)
                       == GET_MODE_BITSIZE (mode)))
            {
              op0 = expand_compound_operation (op0);
-             return gen_unary (NOT, mode,
+             return gen_unary (NOT, mode, mode,
                                gen_lowpart_for_combine (mode, op0));
            }
 
@@ -3856,7 +3887,6 @@ simplify_rtx (x, op0_mode, last, in_dest)
        SUBST (XEXP (x, 0), XEXP (XEXP (x, 0), 0));
       break;
 
-    case LSHIFT:
     case ASHIFT:
     case LSHIFTRT:
     case ASHIFTRT:
@@ -4007,15 +4037,15 @@ simplify_if_then_else (x)
       {
       case GT:
       case GE:
-       return gen_unary (ABS, mode, true);
+       return gen_unary (ABS, mode, mode, true);
       case LT:
       case LE:
-       return gen_unary (NEG, mode, gen_unary (ABS, mode, true));
+       return gen_unary (NEG, mode, mode, gen_unary (ABS, mode, mode, true));
       }
 
   /* Look for MIN or MAX.  */
 
-  if ((! FLOAT_MODE_P (mode) | flag_fast_math)
+  if ((! FLOAT_MODE_P (mode) || flag_fast_math)
       && comparison_p
       && rtx_equal_p (XEXP (cond, 0), true)
       && rtx_equal_p (XEXP (cond, 1), false)
@@ -4043,10 +4073,7 @@ simplify_if_then_else (x)
      C2 = C1 * STORE_FLAG_VALUE. Similarly if OP has an outer ZERO_EXTEND or
      SIGN_EXTEND as long as Z is already extended (so we don't destroy it).
      We can do this kind of thing in some cases when STORE_FLAG_VALUE is
-     neither of the above, but it isn't worth checking for.
-
-     Similarly, (if_then_else COND Z 0) can be replaced by 
-     (mult COND (mult Z STORE_FLAG_VALUE)).  */
+     neither of the above, but it isn't worth checking for.  */
 
   if (comparison_p && mode != VOIDmode && ! side_effects_p (x))
     {
@@ -4058,11 +4085,6 @@ simplify_if_then_else (x)
       enum machine_mode m = mode;
       rtx z = 0, c1;
 
-      if (f == const0_rtx)
-       return gen_binary (MULT, mode, gen_binary (true_code, mode, cond_op0,
-                                                  cond_op1),
-                          gen_binary (MULT, mode, t, const_true_rtx));
-
       if ((GET_CODE (t) == PLUS || GET_CODE (t) == MINUS
           || GET_CODE (t) == IOR || GET_CODE (t) == XOR
           || GET_CODE (t) == ASHIFT
@@ -4157,7 +4179,7 @@ simplify_if_then_else (x)
          temp = gen_binary (op, m, gen_lowpart_for_combine (m, z), temp);
 
          if (extend_op != NIL)
-           temp = gen_unary (extend_op, mode, temp);
+           temp = gen_unary (extend_op, mode, m, temp);
 
          return temp;
        }
@@ -4200,8 +4222,12 @@ simplify_set (x)
   if (GET_CODE (dest) == PC && GET_CODE (src) == RETURN)
     return src;
 
-  /* Convert this into a field assignment operation, if possible.  */
-  x = make_field_assignment (x);
+  /* Now that we know for sure which bits of SRC we are using, see if we can
+     simplify the expression for the object knowing that we only need the
+     low-order bits.  */
+
+  if (GET_MODE_CLASS (mode) == MODE_INT)
+    src = force_to_mode (src, mode, GET_MODE_MASK (mode), NULL_RTX, 0);
 
   /* If we are setting CC0 or if the source is a COMPARE, look for the use of
      the comparison result and try to simplify it unless we already have used
@@ -4214,7 +4240,7 @@ simplify_set (x)
       && (cc_use = find_single_use (dest, subst_insn, &other_insn)) != 0
       && (undobuf.other_insn == 0 || other_insn == undobuf.other_insn)
       && GET_RTX_CLASS (GET_CODE (*cc_use)) == '<'
-      && XEXP (*cc_use, 0) == dest)
+      && rtx_equal_p (XEXP (*cc_use, 0), dest))
     {
       enum rtx_code old_code = GET_CODE (*cc_use);
       enum rtx_code new_code;
@@ -4284,8 +4310,9 @@ simplify_set (x)
              && exact_log2 (mask = nonzero_bits (op0, GET_MODE (op0))) >= 0)
            {
              rtx pat = PATTERN (other_insn), note = 0;
+             int scratches;
 
-             if ((recog_for_combine (&pat, other_insn, &note) < 0
+             if ((recog_for_combine (&pat, other_insn, &note, &scratches) < 0
                   && ! check_asm_operands (pat)))
                {
                  PUT_CODE (*cc_use, old_code);
@@ -4357,6 +4384,14 @@ simplify_set (x)
       && (GET_MODE_SIZE (GET_MODE (src))
          < GET_MODE_SIZE (GET_MODE (SUBREG_REG (src))))
 #endif
+#ifdef CLASS_CANNOT_CHANGE_SIZE
+      && ! (GET_CODE (dest) == REG && REGNO (dest) < FIRST_PSEUDO_REGISTER
+           && (TEST_HARD_REG_BIT
+               (reg_class_contents[(int) CLASS_CANNOT_CHANGE_SIZE],
+                REGNO (dest)))
+           && (GET_MODE_SIZE (GET_MODE (src))
+               != GET_MODE_SIZE (GET_MODE (SUBREG_REG (src)))))
+#endif                           
       && (GET_CODE (dest) == REG
          || (GET_CODE (dest) == SUBREG
              && GET_CODE (SUBREG_REG (dest)) == REG)))
@@ -4389,8 +4424,6 @@ simplify_set (x)
     }
 #endif
 
-#ifndef HAVE_conditional_move
-
   /* If we don't have a conditional move, SET_SRC is an IF_THEN_ELSE, and we
      are comparing an item known to be 0 or -1 against 0, use a logical
      operation instead. Check for one of the arms being an IOR of the other
@@ -4399,8 +4432,13 @@ simplify_set (x)
 
   if (GET_CODE (dest) != PC
       && GET_CODE (src) == IF_THEN_ELSE
+      && GET_MODE_CLASS (GET_MODE (src)) == MODE_INT
       && (GET_CODE (XEXP (src, 0)) == EQ || GET_CODE (XEXP (src, 0)) == NE)
       && XEXP (XEXP (src, 0), 1) == const0_rtx
+      && GET_MODE (src) == GET_MODE (XEXP (XEXP (src, 0), 0))
+#ifdef HAVE_conditional_move
+      && ! can_conditionally_move_p (GET_MODE (src))
+#endif
       && (num_sign_bit_copies (XEXP (XEXP (src, 0), 0),
                               GET_MODE (XEXP (XEXP (src, 0), 0)))
          == GET_MODE_BITSIZE (GET_MODE (XEXP (XEXP (src, 0), 0))))
@@ -4426,7 +4464,7 @@ simplify_set (x)
 
       term2 = gen_binary (AND, GET_MODE (src), XEXP (XEXP (src, 0), 0), true);
       term3 = gen_binary (AND, GET_MODE (src),
-                         gen_unary (NOT, GET_MODE (src),
+                         gen_unary (NOT, GET_MODE (src), GET_MODE (src),
                                     XEXP (XEXP (src, 0), 0)),
                          false);
 
@@ -4437,9 +4475,16 @@ simplify_set (x)
 
       src = SET_SRC (x);
     }
-#endif
 
-  return x;
+  /* If either SRC or DEST is a CLOBBER of (const_int 0), make this
+     whole thing fail.  */
+  if (GET_CODE (src) == CLOBBER && XEXP (src, 0) == const0_rtx)
+    return src;
+  else if (GET_CODE (dest) == CLOBBER && XEXP (dest, 0) == const0_rtx)
+    return dest;
+  else
+    /* Convert this into a field assignment operation, if possible.  */
+    return make_field_assignment (x);
 }
 \f
 /* Simplify, X, and AND, IOR, or XOR operation, and return the simplified
@@ -4462,12 +4507,14 @@ simplify_logical (x, last)
       if (GET_CODE (op0) == XOR
          && rtx_equal_p (XEXP (op0, 0), op1)
          && ! side_effects_p (op1))
-       x = gen_binary (AND, mode, gen_unary (NOT, mode, XEXP (op0, 1)), op1);
+       x = gen_binary (AND, mode,
+                       gen_unary (NOT, mode, mode, XEXP (op0, 1)), op1);
 
       if (GET_CODE (op0) == XOR
          && rtx_equal_p (XEXP (op0, 1), op1)
          && ! side_effects_p (op1))
-       x = gen_binary (AND, mode, gen_unary (NOT, mode, XEXP (op0, 0)), op1);
+       x = gen_binary (AND, mode,
+                       gen_unary (NOT, mode, mode, XEXP (op0, 0)), op1);
 
       /* Similarly for (~ (A ^ B)) & A.  */
       if (GET_CODE (op0) == NOT
@@ -4500,6 +4547,10 @@ simplify_logical (x, last)
 
          if (GET_CODE (x) != AND)
            return x;
+
+         if (GET_RTX_CLASS (GET_CODE (x)) == 'c' 
+             || GET_RTX_CLASS (GET_CODE (x)) == '2')
+           op0 = XEXP (x, 0), op1 = XEXP (x, 1);
        }
 
       /* Convert (A | B) & A to A.  */
@@ -4611,6 +4662,28 @@ simplify_logical (x, last)
                        (GET_CODE (op0) == ASHIFT
                         ? XEXP (op0, 1) : XEXP (op1, 1)));
 
+      /* If OP0 is (ashiftrt (plus ...) C), it might actually be
+        a (sign_extend (plus ...)).  If so, OP1 is a CONST_INT, and the PLUS
+        does not affect any of the bits in OP1, it can really be done
+        as a PLUS and we can associate.  We do this by seeing if OP1
+        can be safely shifted left C bits.  */
+      if (GET_CODE (op1) == CONST_INT && GET_CODE (op0) == ASHIFTRT
+         && GET_CODE (XEXP (op0, 0)) == PLUS
+         && GET_CODE (XEXP (XEXP (op0, 0), 1)) == CONST_INT
+         && GET_CODE (XEXP (op0, 1)) == CONST_INT
+         && INTVAL (XEXP (op0, 1)) < HOST_BITS_PER_WIDE_INT)
+       {
+         int count = INTVAL (XEXP (op0, 1));
+         HOST_WIDE_INT mask = INTVAL (op1) << count;
+
+         if (mask >> count == INTVAL (op1)
+             && (mask & nonzero_bits (XEXP (op0, 0), mode)) == 0)
+           {
+             SUBST (XEXP (XEXP (op0, 0), 1),
+                    GEN_INT (INTVAL (XEXP (XEXP (op0, 0), 1)) | mask));
+             return op0;
+           }
+       }
       break;
 
     case XOR:
@@ -4631,7 +4704,7 @@ simplify_logical (x, last)
            SUBST (XEXP (x, 1), op1);
          }
        else if (num_negated == 1)
-         return gen_unary (NOT, mode, gen_binary (XOR, mode, op0, op1));
+         return gen_unary (NOT, mode, mode, gen_binary (XOR, mode, op0, op1));
       }
 
       /* Convert (xor (and A B) B) to (and (not A) B).  The latter may
@@ -4641,13 +4714,15 @@ simplify_logical (x, last)
       if (GET_CODE (op0) == AND
          && rtx_equal_p (XEXP (op0, 1), op1)
          && ! side_effects_p (op1))
-       return gen_binary (AND, mode, gen_unary (NOT, mode, XEXP (op0, 0)),
+       return gen_binary (AND, mode,
+                          gen_unary (NOT, mode, mode, XEXP (op0, 0)),
                           op1);
 
       else if (GET_CODE (op0) == AND
               && rtx_equal_p (XEXP (op0, 0), op1)
               && ! side_effects_p (op1))
-       return gen_binary (AND, mode, gen_unary (NOT, mode, XEXP (op0, 1)),
+       return gen_binary (AND, mode,
+                          gen_unary (NOT, mode, mode, XEXP (op0, 1)),
                           op1);
 
 #if STORE_FLAG_VALUE == 1
@@ -4766,9 +4841,9 @@ expand_compound_operation (x)
       if (len + pos > GET_MODE_BITSIZE (GET_MODE (XEXP (x, 0))))
        SUBST (XEXP (x, 0), gen_rtx (USE, GET_MODE (x), XEXP (x, 0)));
 
-#if BITS_BIG_ENDIAN
-      pos = GET_MODE_BITSIZE (GET_MODE (XEXP (x, 0))) - len - pos;
-#endif
+      if (BITS_BIG_ENDIAN)
+       pos = GET_MODE_BITSIZE (GET_MODE (XEXP (x, 0))) - len - pos;
+
       break;
 
     default:
@@ -4860,22 +4935,23 @@ expand_field_assignment (x)
              && INTVAL (pos) + len > GET_MODE_BITSIZE (GET_MODE (inner)))
            inner = gen_rtx (USE, GET_MODE (SET_DEST (x)), inner);
 
-#if BITS_BIG_ENDIAN
-         if (GET_CODE (pos) == CONST_INT)
-           pos = GEN_INT (GET_MODE_BITSIZE (GET_MODE (inner)) - len
-                          - INTVAL (pos));
-         else if (GET_CODE (pos) == MINUS
-                  && GET_CODE (XEXP (pos, 1)) == CONST_INT
-                  && (INTVAL (XEXP (pos, 1))
-                      == GET_MODE_BITSIZE (GET_MODE (inner)) - len))
-           /* If position is ADJUST - X, new position is X.  */
-           pos = XEXP (pos, 0);
-         else
-           pos = gen_binary (MINUS, GET_MODE (pos),
-                             GEN_INT (GET_MODE_BITSIZE (GET_MODE (inner))
-                                      - len),
-                             pos);
-#endif
+         if (BITS_BIG_ENDIAN)
+           {
+             if (GET_CODE (pos) == CONST_INT)
+               pos = GEN_INT (GET_MODE_BITSIZE (GET_MODE (inner)) - len
+                              - INTVAL (pos));
+             else if (GET_CODE (pos) == MINUS
+                      && GET_CODE (XEXP (pos, 1)) == CONST_INT
+                      && (INTVAL (XEXP (pos, 1))
+                          == GET_MODE_BITSIZE (GET_MODE (inner)) - len))
+               /* If position is ADJUST - X, new position is X.  */
+               pos = XEXP (pos, 0);
+             else
+               pos = gen_binary (MINUS, GET_MODE (pos),
+                                 GEN_INT (GET_MODE_BITSIZE (GET_MODE (inner))
+                                          - len),
+                                 pos);
+           }
        }
 
       /* A SUBREG between two modes that occupy the same numbers of words
@@ -4912,6 +4988,7 @@ expand_field_assignment (x)
                   gen_binary (IOR, compute_mode,
                               gen_binary (AND, compute_mode,
                                           gen_unary (NOT, compute_mode,
+                                                     compute_mode,
                                                      gen_binary (ASHIFT,
                                                                  compute_mode,
                                                                  mask, pos)),
@@ -5053,14 +5130,20 @@ make_extraction (mode, inner, pos, pos_rtx, len,
          MEM_IN_STRUCT_P (new) = MEM_IN_STRUCT_P (inner);
        }
       else if (GET_CODE (inner) == REG)
-       /* We can't call gen_lowpart_for_combine here since we always want
-          a SUBREG and it would sometimes return a new hard register.  */
-       new = gen_rtx (SUBREG, tmode, inner,
-                      (WORDS_BIG_ENDIAN
-                       && GET_MODE_SIZE (inner_mode) > UNITS_PER_WORD
-                       ? ((GET_MODE_SIZE (inner_mode) - GET_MODE_SIZE (tmode))
-                          / UNITS_PER_WORD)
-                       : 0));
+       {
+         /* We can't call gen_lowpart_for_combine here since we always want
+            a SUBREG and it would sometimes return a new hard register.  */
+         if (tmode != inner_mode)
+           new = gen_rtx (SUBREG, tmode, inner,
+                          (WORDS_BIG_ENDIAN
+                           && GET_MODE_SIZE (inner_mode) > UNITS_PER_WORD
+                           ? ((GET_MODE_SIZE (inner_mode)
+                               - GET_MODE_SIZE (tmode))
+                              / UNITS_PER_WORD)
+                           : 0));
+         else
+           new = inner;
+       }
       else
        new = force_to_mode (inner, tmode,
                             len >= HOST_BITS_PER_WIDE_INT
@@ -5151,20 +5234,22 @@ make_extraction (mode, inner, pos, pos_rtx, len,
 
   orig_pos = pos;
 
-#if BITS_BIG_ENDIAN
-  /* If position is constant, compute new position.  Otherwise, build
-     subtraction.  */
-  if (pos_rtx == 0)
-    pos = (MAX (GET_MODE_BITSIZE (is_mode), GET_MODE_BITSIZE (wanted_mem_mode))
-          - len - pos);
-  else
-    pos_rtx
-      = gen_rtx_combine (MINUS, GET_MODE (pos_rtx),
-                        GEN_INT (MAX (GET_MODE_BITSIZE (is_mode),
-                                      GET_MODE_BITSIZE (wanted_mem_mode))
-                                 - len),
-                        pos_rtx);
-#endif
+  if (BITS_BIG_ENDIAN)
+    {
+      /* If position is constant, compute new position.  Otherwise,
+        build subtraction.  */
+      if (pos_rtx == 0)
+       pos = (MAX (GET_MODE_BITSIZE (is_mode),
+                   GET_MODE_BITSIZE (wanted_mem_mode))
+              - len - pos);
+      else
+       pos_rtx
+         = gen_rtx_combine (MINUS, GET_MODE (pos_rtx),
+                            GEN_INT (MAX (GET_MODE_BITSIZE (is_mode),
+                                          GET_MODE_BITSIZE (wanted_mem_mode))
+                                     - len),
+                            pos_rtx);
+    }
 
   /* If INNER has a wider mode, make it smaller.  If this is a constant
      extract, try to adjust the byte to point to the byte containing
@@ -5184,11 +5269,10 @@ make_extraction (mode, inner, pos, pos_rtx, len,
             
       /* If bytes are big endian and we had a paradoxical SUBREG, we must
         adjust OFFSET to compensate. */
-#if BYTES_BIG_ENDIAN
-      if (! spans_byte
+      if (BYTES_BIG_ENDIAN
+         && ! spans_byte
          && GET_MODE_SIZE (inner_mode) < GET_MODE_SIZE (is_mode))
        offset -= GET_MODE_SIZE (is_mode) - GET_MODE_SIZE (inner_mode);
-#endif
 
       /* If this is a constant position, we can move to the desired byte.  */
       if (pos_rtx == 0)
@@ -5197,11 +5281,11 @@ make_extraction (mode, inner, pos, pos_rtx, len,
          pos %= GET_MODE_BITSIZE (wanted_mem_mode);
        }
 
-#if BYTES_BIG_ENDIAN != BITS_BIG_ENDIAN
-      if (! spans_byte && is_mode != wanted_mem_mode)
+      if (BYTES_BIG_ENDIAN != BITS_BIG_ENDIAN
+         && ! spans_byte
+         && is_mode != wanted_mem_mode)
        offset = (GET_MODE_SIZE (is_mode)
                  - GET_MODE_SIZE (wanted_mem_mode) - offset);
-#endif
 
       if (offset != 0 || inner_mode != wanted_mem_mode)
        {
@@ -5249,6 +5333,51 @@ make_extraction (mode, inner, pos, pos_rtx, len,
   return new;
 }
 \f
+/* See if X contains an ASHIFT of COUNT or more bits that can be commuted
+   with any other operations in X.  Return X without that shift if so.  */
+
+static rtx
+extract_left_shift (x, count)
+     rtx x;
+     int count;
+{
+  enum rtx_code code = GET_CODE (x);
+  enum machine_mode mode = GET_MODE (x);
+  rtx tem;
+
+  switch (code)
+    {
+    case ASHIFT:
+      /* This is the shift itself.  If it is wide enough, we will return
+        either the value being shifted if the shift count is equal to
+        COUNT or a shift for the difference.  */
+      if (GET_CODE (XEXP (x, 1)) == CONST_INT
+         && INTVAL (XEXP (x, 1)) >= count)
+       return simplify_shift_const (NULL_RTX, ASHIFT, mode, XEXP (x, 0),
+                                    INTVAL (XEXP (x, 1)) - count);
+      break;
+
+    case NEG:  case NOT:
+      if ((tem = extract_left_shift (XEXP (x, 0), count)) != 0)
+       return gen_unary (code, mode, mode, tem);
+
+      break;
+
+    case PLUS:  case IOR:  case XOR:  case AND:
+      /* If we can safely shift this constant and we find the inner shift,
+        make a new operation.  */
+      if (GET_CODE (XEXP (x,1)) == CONST_INT
+         && (INTVAL (XEXP (x, 1)) & (((HOST_WIDE_INT) 1 << count)) - 1) == 0
+         && (tem = extract_left_shift (XEXP (x, 0), count)) != 0)
+       return gen_binary (code, mode, tem, 
+                          GEN_INT (INTVAL (XEXP (x, 1)) >> count));
+
+      break;
+    }
+
+  return 0;
+}
+\f
 /* Look at the expression rooted at X.  Look for expressions
    equivalent to ZERO_EXTRACT, SIGN_EXTRACT, ZERO_EXTEND, SIGN_EXTEND.
    Form these expressions.
@@ -5275,6 +5404,7 @@ make_compound_operation (x, in_code)
   enum rtx_code code = GET_CODE (x);
   enum machine_mode mode = GET_MODE (x);
   int mode_width = GET_MODE_BITSIZE (mode);
+  rtx rhs, lhs;
   enum rtx_code next_code;
   int i;
   rtx new = 0;
@@ -5296,7 +5426,6 @@ make_compound_operation (x, in_code)
   switch (code)
     {
     case ASHIFT:
-    case LSHIFT:
       /* Convert shifts by constants into multiplications if inside
         an address.  */
       if (in_code == MEM && GET_CODE (XEXP (x, 1)) == CONST_INT
@@ -5338,7 +5467,7 @@ make_compound_operation (x, in_code)
                                 XEXP (SUBREG_REG (XEXP (x, 0)), 1), i, 1,
                                 0, in_code == COMPARE);
        }
-      /* Same as previous, but for (xor/ior (lshift...) (lshift...)).  */
+      /* Same as previous, but for (xor/ior (lshiftrt...) (lshiftrt...)).  */
       else if ((GET_CODE (XEXP (x, 0)) == XOR
                || GET_CODE (XEXP (x, 0)) == IOR)
               && GET_CODE (XEXP (XEXP (x, 0), 0)) == LSHIFTRT
@@ -5431,81 +5560,38 @@ make_compound_operation (x, in_code)
       /* ... fall through ... */
 
     case ASHIFTRT:
+      lhs = XEXP (x, 0);
+      rhs = XEXP (x, 1);
+
       /* If we have (ashiftrt (ashift foo C1) C2) with C2 >= C1,
         this is a SIGN_EXTRACT.  */
-      if (GET_CODE (XEXP (x, 1)) == CONST_INT
-         && GET_CODE (XEXP (x, 0)) == ASHIFT
-         && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT
-         && INTVAL (XEXP (x, 1)) >= INTVAL (XEXP (XEXP (x, 0), 1)))
+      if (GET_CODE (rhs) == CONST_INT
+         && GET_CODE (lhs) == ASHIFT
+         && GET_CODE (XEXP (lhs, 1)) == CONST_INT
+         && INTVAL (rhs) >= INTVAL (XEXP (lhs, 1)))
        {
-         new = make_compound_operation (XEXP (XEXP (x, 0), 0), next_code);
+         new = make_compound_operation (XEXP (lhs, 0), next_code);
          new = make_extraction (mode, new,
-                                (INTVAL (XEXP (x, 1))
-                                 - INTVAL (XEXP (XEXP (x, 0), 1))),
-                                NULL_RTX, mode_width - INTVAL (XEXP (x, 1)),
-                                code == LSHIFTRT, 0, in_code == COMPARE);
-       }
-
-      /* Similarly if we have (ashifrt (OP (ashift foo C1) C3) C2).  In these
-        cases, we are better off returning a SIGN_EXTEND of the operation.  */
-
-      if (GET_CODE (XEXP (x, 1)) == CONST_INT
-         && (GET_CODE (XEXP (x, 0)) == IOR || GET_CODE (XEXP (x, 0)) == AND
-             || GET_CODE (XEXP (x, 0)) == XOR
-             || GET_CODE (XEXP (x, 0)) == PLUS)
-         && GET_CODE (XEXP (XEXP (x, 0), 0)) == ASHIFT
-         && GET_CODE (XEXP (XEXP (XEXP (x, 0), 0), 1)) == CONST_INT
-         && INTVAL (XEXP (XEXP (XEXP (x, 0), 0), 1)) < HOST_BITS_PER_WIDE_INT
-         && GET_CODE (XEXP (XEXP (x, 0), 1)) == CONST_INT
-         && 0 == (INTVAL (XEXP (XEXP (x, 0), 1))
-                  & (((HOST_WIDE_INT) 1
-                      << (MIN (INTVAL (XEXP (XEXP (XEXP (x, 0), 0), 1)),
-                               INTVAL (XEXP (x, 1)))
-                          - 1)))))
-       {
-         rtx c1 = XEXP (XEXP (XEXP (x, 0), 0), 1);
-         rtx c2 = XEXP (x, 1);
-         rtx c3 = XEXP (XEXP (x, 0), 1);
-         HOST_WIDE_INT newop1;
-         rtx inner = XEXP (XEXP (XEXP (x, 0), 0), 0);
-
-         /* If C1 > C2, INNER needs to have the shift performed on it
-            for C1-C2 bits.  */
-         if (INTVAL (c1) > INTVAL (c2))
-           {
-             inner = gen_binary (ASHIFT, mode, inner,
-                                 GEN_INT (INTVAL (c1) - INTVAL (c2)));
-             c1 = c2;
-           }
-
-         newop1 = INTVAL (c3) >> INTVAL (c1);
-         new = make_compound_operation (inner,
-                                        GET_CODE (XEXP (x, 0)) == PLUS
-                                        ? MEM : GET_CODE (XEXP (x, 0)));
-         new = make_extraction (mode,
-                                gen_binary (GET_CODE (XEXP (x, 0)), mode, new,
-                                            GEN_INT (newop1)),
-                                INTVAL (c2) - INTVAL (c1),
-                                NULL_RTX, mode_width - INTVAL (c2),
+                                INTVAL (rhs) - INTVAL (XEXP (lhs, 1)),
+                                NULL_RTX, mode_width - INTVAL (rhs),
                                 code == LSHIFTRT, 0, in_code == COMPARE);
        }
 
-      /* Similarly for (ashiftrt (neg (ashift FOO C1)) C2).  */
-      if (GET_CODE (XEXP (x, 1)) == CONST_INT
-         && GET_CODE (XEXP (x, 0)) == NEG
-         && GET_CODE (XEXP (XEXP (x, 0), 0)) == ASHIFT
-         && GET_CODE (XEXP (XEXP (XEXP (x, 0), 0), 1)) == CONST_INT
-         && INTVAL (XEXP (x, 1)) >= INTVAL (XEXP (XEXP (XEXP (x, 0), 0), 1)))
-       {
-         new = make_compound_operation (XEXP (XEXP (XEXP (x, 0), 0), 0),
-                                        next_code);
-         new = make_extraction (mode,
-                                gen_unary (GET_CODE (XEXP (x, 0)), mode, new),
-                                (INTVAL (XEXP (x, 1))
-                                 - INTVAL (XEXP (XEXP (XEXP (x, 0), 0), 1))),
-                                NULL_RTX, mode_width - INTVAL (XEXP (x, 1)),
-                                code == LSHIFTRT, 0, in_code == COMPARE);
-       }
+      /* See if we have operations between an ASHIFTRT and an ASHIFT.
+        If so, try to merge the shifts into a SIGN_EXTEND.  We could
+        also do this for some cases of SIGN_EXTRACT, but it doesn't
+        seem worth the effort; the case checked for occurs on Alpha.  */
+      
+      if (GET_RTX_CLASS (GET_CODE (lhs)) != 'o'
+         && ! (GET_CODE (lhs) == SUBREG
+               && (GET_RTX_CLASS (GET_CODE (SUBREG_REG (lhs))) == 'o'))
+         && GET_CODE (rhs) == CONST_INT
+         && INTVAL (rhs) < HOST_BITS_PER_WIDE_INT
+         && (new = extract_left_shift (lhs, INTVAL (rhs))) != 0)
+       new = make_extraction (mode, make_compound_operation (new, next_code),
+                              0, NULL_RTX, mode_width - INTVAL (rhs),
+                              code == LSHIFTRT, 0, in_code == COMPARE);
+       
       break;
 
     case SUBREG:
@@ -5590,7 +5676,7 @@ get_pos_from_mask (m, plen)
 
    If JUST_SELECT is nonzero, don't optimize by noticing that bits in MASK
    are all off in X.  This is used when X will be complemented, by either
-   NOT or XOR.  */
+   NOT, NEG, or XOR.  */
 
 static rtx
 force_to_mode (x, mode, mask, reg, just_select)
@@ -5601,15 +5687,21 @@ force_to_mode (x, mode, mask, reg, just_select)
      int just_select;
 {
   enum rtx_code code = GET_CODE (x);
-  int next_select = just_select || code == XOR || code == NOT;
+  int next_select = just_select || code == XOR || code == NOT || code == NEG;
   enum machine_mode op_mode;
   unsigned HOST_WIDE_INT fuller_mask, nonzero;
   rtx op0, op1, temp;
 
+  /* If this is a CALL, don't do anything.  Some of the code below
+     will do the wrong thing since the mode of a CALL is VOIDmode.  */
+  if (code == CALL)
+    return x;
+
   /* We want to perform the operation is its present mode unless we know
      that the operation is valid in MODE, in which case we do the operation
      in MODE.  */
-  op_mode = ((code_to_optab[(int) code] != 0
+  op_mode = ((GET_MODE_CLASS (mode) == GET_MODE_CLASS (GET_MODE (x))
+             && code_to_optab[(int) code] != 0
              && (code_to_optab[(int) code]->handlers[(int) mode].insn_code
                  != CODE_FOR_nothing))
             ? mode : GET_MODE (x));
@@ -5657,13 +5749,15 @@ force_to_mode (x, mode, mask, reg, just_select)
       return GEN_INT (cval);
     }
 
-  /* If X is narrower than MODE, just get X in the proper mode.  */
-  if (GET_MODE_SIZE (GET_MODE (x)) < GET_MODE_SIZE (mode))
+  /* If X is narrower than MODE and we want all the bits in X's mode, just
+     get X in the proper mode.  */
+  if (GET_MODE_SIZE (GET_MODE (x)) < GET_MODE_SIZE (mode)
+      && (GET_MODE_MASK (GET_MODE (x)) & ~ mask) == 0)
     return gen_lowpart_for_combine (mode, x);
 
-  /* If we aren't changing the mode and all zero bits in MASK are already
-     known to be zero in X, we need not do anything.  */
-  if (GET_MODE (x) == mode && (~ mask & nonzero) == 0)
+  /* If we aren't changing the mode, X is not a SUBREG, and all zero bits in
+     MASK are already known to be zero in X, we need not do anything.  */
+  if (GET_MODE (x) == mode && code != SUBREG && (~ mask & nonzero) == 0)
     return x;
 
   switch (code)
@@ -5673,14 +5767,14 @@ force_to_mode (x, mode, mask, reg, just_select)
         generating something that won't match. */
       return x;
 
-#if ! BITS_BIG_ENDIAN
     case USE:
       /* X is a (use (mem ..)) that was made from a bit-field extraction that
         spanned the boundary of the MEM.  If we are now masking so it is
         within that boundary, we don't need the USE any more.  */
-      if ((mask & ~ GET_MODE_MASK (GET_MODE (XEXP (x, 0)))) == 0)
+      if (! BITS_BIG_ENDIAN
+         && (mask & ~ GET_MODE_MASK (GET_MODE (XEXP (x, 0)))) == 0)
        return force_to_mode (XEXP (x, 0), mode, mask, reg, next_select);
-#endif
+      break;
 
     case SIGN_EXTEND:
     case ZERO_EXTEND:
@@ -5699,18 +5793,14 @@ force_to_mode (x, mode, mask, reg, just_select)
 
     case SUBREG:
       if (subreg_lowpart_p (x)
-         /* We can ignore the effect this SUBREG if it narrows the mode or,
-            on machines where register operations are performed on the full
-            word, if the constant masks to zero all the bits the mode
-            doesn't have.  */
+         /* We can ignore the effect of this SUBREG if it narrows the mode or
+            if the constant masks to zero all the bits the mode doesn't
+            have.  */
          && ((GET_MODE_SIZE (GET_MODE (x))
               < GET_MODE_SIZE (GET_MODE (SUBREG_REG (x))))
-#ifdef WORD_REGISTER_OPERATIONS
              || (0 == (mask
                        & GET_MODE_MASK (GET_MODE (x))
-                       & ~ GET_MODE_MASK (GET_MODE (SUBREG_REG (x)))))
-#endif
-             ))
+                       & ~ GET_MODE_MASK (GET_MODE (SUBREG_REG (x)))))))
        return force_to_mode (SUBREG_REG (x), mode, mask, reg, next_select);
       break;
 
@@ -5719,20 +5809,44 @@ force_to_mode (x, mode, mask, reg, just_select)
         whose constant is the AND of that constant with MASK.  If it
         remains an AND of MASK, delete it since it is redundant.  */
 
-      if (GET_CODE (XEXP (x, 1)) == CONST_INT
-         && GET_MODE_BITSIZE (GET_MODE (x)) <= HOST_BITS_PER_WIDE_INT)
+      if (GET_CODE (XEXP (x, 1)) == CONST_INT)
        {
          x = simplify_and_const_int (x, op_mode, XEXP (x, 0),
                                      mask & INTVAL (XEXP (x, 1)));
 
          /* If X is still an AND, see if it is an AND with a mask that
-            is just some low-order bits.  If so, and it is BITS wide (it
-            can't be wider), we don't need it.  */
+            is just some low-order bits.  If so, and it is MASK, we don't
+            need it.  */
 
          if (GET_CODE (x) == AND && GET_CODE (XEXP (x, 1)) == CONST_INT
              && INTVAL (XEXP (x, 1)) == mask)
            x = XEXP (x, 0);
 
+         /* If it remains an AND, try making another AND with the bits
+            in the mode mask that aren't in MASK turned on.  If the
+            constant in the AND is wide enough, this might make a
+            cheaper constant.  */
+
+         if (GET_CODE (x) == AND && GET_CODE (XEXP (x, 1)) == CONST_INT
+             && GET_MODE_MASK (GET_MODE (x)) != mask
+             && GET_MODE_BITSIZE (GET_MODE (x)) <= HOST_BITS_PER_WIDE_INT)
+           {
+             HOST_WIDE_INT cval = (INTVAL (XEXP (x, 1))
+                                   | (GET_MODE_MASK (GET_MODE (x)) & ~ mask));
+             int width = GET_MODE_BITSIZE (GET_MODE (x));
+             rtx y;
+
+             /* If MODE is narrower that HOST_WIDE_INT and CVAL is a negative
+                number, sign extend it.  */
+             if (width > 0 && width < HOST_BITS_PER_WIDE_INT
+                 && (cval & ((HOST_WIDE_INT) 1 << (width - 1))) != 0)
+               cval |= (HOST_WIDE_INT) -1 << width;
+
+             y = gen_binary (AND, GET_MODE (x), XEXP (x, 0), GEN_INT (cval));
+             if (rtx_cost (y, SET) < rtx_cost (x, SET))
+               x = y;
+           }
+
          break;
        }
 
@@ -5743,13 +5857,26 @@ force_to_mode (x, mode, mask, reg, just_select)
         low-order bits (as in an alignment operation) and FOO is already
         aligned to that boundary, mask C1 to that boundary as well.
         This may eliminate that PLUS and, later, the AND.  */
-      if (GET_CODE (XEXP (x, 1)) == CONST_INT
-         && exact_log2 (- mask) >= 0
-         && (nonzero_bits (XEXP (x, 0), mode) & ~ mask) == 0
-         && (INTVAL (XEXP (x, 1)) & ~ mask) != 0)
-       return force_to_mode (plus_constant (XEXP (x, 0),
-                                            INTVAL (XEXP (x, 1)) & mask),
-                             mode, mask, reg, next_select);
+
+      {
+       int width = GET_MODE_BITSIZE (mode);
+       unsigned HOST_WIDE_INT smask = mask;
+
+       /* If MODE is narrower than HOST_WIDE_INT and mask is a negative
+          number, sign extend it.  */
+
+       if (width < HOST_BITS_PER_WIDE_INT
+           && (smask & ((HOST_WIDE_INT) 1 << (width - 1))) != 0)
+         smask |= (HOST_WIDE_INT) -1 << width;
+
+       if (GET_CODE (XEXP (x, 1)) == CONST_INT
+           && exact_log2 (- smask) >= 0
+           && (nonzero_bits (XEXP (x, 0), mode) & ~ mask) == 0
+           && (INTVAL (XEXP (x, 1)) & ~ mask) != 0)
+         return force_to_mode (plus_constant (XEXP (x, 0),
+                                              INTVAL (XEXP (x, 1)) & mask),
+                               mode, mask, reg, next_select);
+      }
 
       /* ... fall through ... */
 
@@ -5811,7 +5938,6 @@ force_to_mode (x, mode, mask, reg, just_select)
       break;
 
     case ASHIFT:
-    case LSHIFT:
       /* For left shifts, do the same, but just for the first operand.
         However, we cannot do anything with shifts where we cannot
         guarantee that the counts are smaller than the size of the mode
@@ -5892,8 +6018,9 @@ force_to_mode (x, mode, mask, reg, just_select)
     case ASHIFTRT:
       /* If we are just looking for the sign bit, we don't need this shift at
         all, even if it has a variable count.  */
-      if (mask == ((HOST_WIDE_INT) 1
-                  << (GET_MODE_BITSIZE (GET_MODE (x)) - 1)))
+      if (GET_MODE_BITSIZE (GET_MODE (x)) <= HOST_BITS_PER_WIDE_INT
+         && (mask == ((HOST_WIDE_INT) 1
+                      << (GET_MODE_BITSIZE (GET_MODE (x)) - 1))))
        return force_to_mode (XEXP (x, 0), mode, mask, reg, next_select);
 
       /* If this is a shift by a constant, get a mask that contains those bits
@@ -5958,7 +6085,7 @@ force_to_mode (x, mode, mask, reg, just_select)
          temp = simplify_binary_operation (code == ROTATE ? ROTATERT : ROTATE,
                                            GET_MODE (x), GEN_INT (mask),
                                            XEXP (x, 1));
-         if (temp)
+         if (temp && GET_CODE(temp) == CONST_INT)
            SUBST (XEXP (x, 0),
                   force_to_mode (XEXP (x, 0), GET_MODE (x),
                                  INTVAL (temp), reg, next_select));
@@ -5966,6 +6093,11 @@ force_to_mode (x, mode, mask, reg, just_select)
       break;
        
     case NEG:
+      /* If we just want the low-order bit, the NEG isn't needed since it
+        won't change the low-order bit.    */
+      if (mask == 1)
+       return force_to_mode (XEXP (x, 0), mode, mask, reg, just_select);
+
       /* We need any bits less significant than the most significant bit in
         MASK since carries from those bits will affect the bits we are
         interested in.  */
@@ -5996,7 +6128,7 @@ force_to_mode (x, mode, mask, reg, just_select)
                                     force_to_mode (XEXP (x, 0), mode, mask,
                                                    reg, next_select));
       if (op_mode != GET_MODE (x) || op0 != XEXP (x, 0))
-       x = gen_unary (code, op_mode, op0);
+       x = gen_unary (code, op_mode, op_mode, op0);
       break;
 
     case NE:
@@ -6051,13 +6183,13 @@ if_then_else_cond (x, ptrue, pfalse)
   if (GET_RTX_CLASS (code) == '1'
       && (cond0 = if_then_else_cond (XEXP (x, 0), &true0, &false0)) != 0)
     {
-      *ptrue = gen_unary (code, mode, true0);
-      *pfalse = gen_unary (code, mode, false0);
+      *ptrue = gen_unary (code, mode, GET_MODE (XEXP (x, 0)), true0);
+      *pfalse = gen_unary (code, mode, GET_MODE (XEXP (x, 0)), false0);
       return cond0;
     }
 
   /* If this is a COMPARE, do nothing, since the IF_THEN_ELSE we would
-     make can't possibly match and would supress other optimizations.  */
+     make can't possibly match and would suppress other optimizations.  */
   else if (code == COMPARE)
     ;
 
@@ -6108,7 +6240,7 @@ if_then_else_cond (x, ptrue, pfalse)
              *ptrue = gen_binary (MULT, mode, op0, const_true_rtx);
              *pfalse = gen_binary (MULT, mode, 
                                    (code == MINUS 
-                                    ? gen_unary (NEG, mode, op1) : op1),
+                                    ? gen_unary (NEG, mode, mode, op1) : op1),
                                    const_true_rtx);
              return cond0;
            }
@@ -6234,7 +6366,8 @@ known_cond (x, cond, reg, val)
       case GE:  case GT:  case EQ:
        return XEXP (x, 0);
       case LT:  case LE:
-       return gen_unary (NEG, GET_MODE (XEXP (x, 0)), XEXP (x, 0));
+       return gen_unary (NEG, GET_MODE (XEXP (x, 0)), GET_MODE (XEXP (x, 0)),
+                         XEXP (x, 0));
       }
 
   /* The only other cases we handle are MIN, MAX, and comparisons if the
@@ -6458,8 +6591,7 @@ apply_distributive_law (x)
       break;
 
     case ASHIFT:
-    case LSHIFT:
-      /* These are also multiplies, so they distribute over everything.  */
+      /* This is also a multiply, so it distributes over everything.  */
       break;
 
     case SUBREG:
@@ -6480,7 +6612,7 @@ apply_distributive_law (x)
          || (GET_MODE_CLASS (GET_MODE (lhs))
              != GET_MODE_CLASS (GET_MODE (SUBREG_REG (lhs))))
          || (GET_MODE_SIZE (GET_MODE (lhs))
-             < GET_MODE_SIZE (GET_MODE (SUBREG_REG (lhs))))
+             > GET_MODE_SIZE (GET_MODE (SUBREG_REG (lhs))))
          || GET_MODE_SIZE (GET_MODE (SUBREG_REG (lhs))) > UNITS_PER_WORD)
        return x;
 
@@ -6518,7 +6650,7 @@ apply_distributive_law (x)
   if (code == XOR && inner_code == IOR)
     {
       inner_code = AND;
-      other = gen_unary (NOT, GET_MODE (x), other);
+      other = gen_unary (NOT, GET_MODE (x), GET_MODE (x), other);
     }
 
   /* We may be able to continuing distributing the result, so call
@@ -6542,6 +6674,7 @@ simplify_and_const_int (x, mode, varop, constop)
      unsigned HOST_WIDE_INT constop;
 {
   unsigned HOST_WIDE_INT nonzero;
+  int width = GET_MODE_BITSIZE (mode);
   int i;
 
   /* Simplify VAROP knowing that we will be only looking at some of the
@@ -6559,6 +6692,19 @@ simplify_and_const_int (x, mode, varop, constop)
 
   nonzero = nonzero_bits (varop, mode) & GET_MODE_MASK (mode);
 
+  /* If this would be an entire word for the target, but is not for
+     the host, then sign-extend on the host so that the number will look
+     the same way on the host that it would on the target.
+
+     For example, when building a 64 bit alpha hosted 32 bit sparc
+     targeted compiler, then we want the 32 bit unsigned value -1 to be
+     represented as a 64 bit value -1, and not as 0x00000000ffffffff.
+     The later confuses the sparc backend.  */
+
+  if (BITS_PER_WORD < HOST_BITS_PER_WIDE_INT && BITS_PER_WORD == width
+      && (nonzero & ((HOST_WIDE_INT) 1 << (width - 1))))
+    nonzero |= ((HOST_WIDE_INT) (-1) << width);
+
   /* Turn off all bits in the constant that are known to already be zero.
      Thus, if the AND isn't needed at all, we will have CONSTOP == NONZERO_BITS
      which is tested below.  */
@@ -6642,6 +6788,10 @@ nonzero_bits (x, mode)
   int mode_width = GET_MODE_BITSIZE (mode);
   rtx tem;
 
+  /* For floating-point values, assume all bits are needed.  */
+  if (FLOAT_MODE_P (GET_MODE (x)) || FLOAT_MODE_P (mode))
+    return nonzero;
+
   /* If X is wider than MODE, use its mode instead.  */
   if (GET_MODE_BITSIZE (GET_MODE (x)) > mode_width)
     {
@@ -6692,10 +6842,18 @@ nonzero_bits (x, mode)
          sp_alignment = MIN (PUSH_ROUNDING (1), sp_alignment);
 #endif
 
-         return nonzero & ~ (sp_alignment - 1);
+         nonzero &= ~ (sp_alignment - 1);
        }
 #endif
 
+#ifdef POINTERS_EXTEND_UNSIGNED
+      /* If pointers extend unsigned and this is a pointer in Pmode, say that
+        all the bits above ptr_mode are known to be zero.  */
+      if (POINTERS_EXTEND_UNSIGNED && GET_MODE (x) == Pmode
+         && REGNO_POINTER_FLAG (REGNO (x)))
+       nonzero &= GET_MODE_MASK (ptr_mode);
+#endif
+
       /* If X is a register whose nonzero bits value is current, use it.
         Otherwise, if X is a register whose value we can find, use that
         value.  Otherwise, use the previously-computed global nonzero bits
@@ -6843,8 +7001,10 @@ nonzero_bits (x, mode)
        int width1 = floor_log2 (nz1) + 1;
        int low0 = floor_log2 (nz0 & -nz0);
        int low1 = floor_log2 (nz1 & -nz1);
-       int op0_maybe_minusp = (nz0 & ((HOST_WIDE_INT) 1 << (mode_width - 1)));
-       int op1_maybe_minusp = (nz1 & ((HOST_WIDE_INT) 1 << (mode_width - 1)));
+       HOST_WIDE_INT op0_maybe_minusp
+         = (nz0 & ((HOST_WIDE_INT) 1 << (mode_width - 1)));
+       HOST_WIDE_INT op1_maybe_minusp
+         = (nz1 & ((HOST_WIDE_INT) 1 << (mode_width - 1)));
        int result_width = mode_width;
        int result_low = 0;
 
@@ -6926,7 +7086,6 @@ nonzero_bits (x, mode)
     case ASHIFTRT:
     case LSHIFTRT:
     case ASHIFT:
-    case LSHIFT:
     case ROTATE:
       /* The nonzero bits are in two classes: any bits within MODE
         that aren't in GET_MODE (x) are always significant.  The rest of the
@@ -6961,7 +7120,7 @@ nonzero_bits (x, mode)
              if (inner & ((HOST_WIDE_INT) 1 << (width - 1 - count)))
                inner |= (((HOST_WIDE_INT) 1 << count) - 1) << (width - count);
            }
-         else if (code == LSHIFT || code == ASHIFT)
+         else if (code == ASHIFT)
            inner <<= count;
          else
            inner = ((inner << (count % width)
@@ -7002,12 +7161,13 @@ num_sign_bit_copies (x, mode)
   rtx tem;
 
   /* If we weren't given a mode, use the mode of X.  If the mode is still
-     VOIDmode, we don't know anything.  */
+     VOIDmode, we don't know anything.  Likewise if one of the modes is
+     floating-point.  */
 
   if (mode == VOIDmode)
     mode = GET_MODE (x);
 
-  if (mode == VOIDmode)
+  if (mode == VOIDmode || FLOAT_MODE_P (mode) || FLOAT_MODE_P (GET_MODE (x)))
     return 1;
 
   bitwidth = GET_MODE_BITSIZE (mode);
@@ -7029,6 +7189,14 @@ num_sign_bit_copies (x, mode)
     {
     case REG:
 
+#ifdef POINTERS_EXTEND_UNSIGNED
+      /* If pointers extend signed and this is a pointer in Pmode, say that
+        all the bits above ptr_mode are known to be sign bit copies.  */
+      if (! POINTERS_EXTEND_UNSIGNED && GET_MODE (x) == Pmode && mode == Pmode
+         && REGNO_POINTER_FLAG (REGNO (x)))
+       return GET_MODE_BITSIZE (Pmode) - GET_MODE_BITSIZE (ptr_mode) + 1;
+#endif
+
       if (reg_last_set_value[REGNO (x)] != 0
          && reg_last_set_mode[REGNO (x)] == mode
          && (reg_n_sets[REGNO (x)] == 1
@@ -7081,15 +7249,23 @@ num_sign_bit_copies (x, mode)
        }
 
 #ifdef WORD_REGISTER_OPERATIONS
+#ifdef LOAD_EXTEND_OP
       /* For paradoxical SUBREGs on machines where all register operations
         affect the entire register, just look inside.  Note that we are
         passing MODE to the recursive call, so the number of sign bit copies
         will remain relative to that mode, not the inner mode.  */
 
-      if (GET_MODE_SIZE (GET_MODE (x))
-         > GET_MODE_SIZE (GET_MODE (SUBREG_REG (x))))
+      /* This works only if loads sign extend.  Otherwise, if we get a
+        reload for the inner part, it may be loaded from the stack, and
+        then we lose all sign bit copies that existed before the store
+        to the stack.  */
+
+      if ((GET_MODE_SIZE (GET_MODE (x))
+          > GET_MODE_SIZE (GET_MODE (SUBREG_REG (x))))
+         && LOAD_EXTEND_OP (GET_MODE (SUBREG_REG (x))) == SIGN_EXTEND)
        return num_sign_bit_copies (SUBREG_REG (x), mode);
 #endif
+#endif
       break;
 
     case SIGN_EXTRACT:
@@ -7229,7 +7405,6 @@ num_sign_bit_copies (x, mode)
       return num0;
 
     case ASHIFT:
-    case LSHIFT:
       /* Left shifts destroy copies.  */
       if (GET_CODE (XEXP (x, 1)) != CONST_INT
          || INTVAL (XEXP (x, 1)) < 0
@@ -7323,6 +7498,7 @@ merge_outer_ops (pop0, pconst0, op1, const1, mode, pcomp_p)
 {
   enum rtx_code op0 = *pop0;
   HOST_WIDE_INT const0 = *pconst0;
+  int width = GET_MODE_BITSIZE (mode);
 
   const0 &= GET_MODE_MASK (mode);
   const1 &= GET_MODE_MASK (mode);
@@ -7412,6 +7588,19 @@ merge_outer_ops (pop0, pconst0, op1, const1, mode, pcomp_p)
   else if (const0 == GET_MODE_MASK (mode) && op0 == AND)
     op0 = NIL;
 
+  /* If this would be an entire word for the target, but is not for
+     the host, then sign-extend on the host so that the number will look
+     the same way on the host that it would on the target.
+
+     For example, when building a 64 bit alpha hosted 32 bit sparc
+     targeted compiler, then we want the 32 bit unsigned value -1 to be
+     represented as a 64 bit value -1, and not as 0x00000000ffffffff.
+     The later confuses the sparc backend.  */
+
+  if (BITS_PER_WORD < HOST_BITS_PER_WIDE_INT && BITS_PER_WORD == width
+      && (const0 & ((HOST_WIDE_INT) 1 << (width - 1))))
+    const0 |= ((HOST_WIDE_INT) (-1) << width);
+
   *pop0 = op0;
   *pconst0 = const0;
 
@@ -7473,19 +7662,17 @@ simplify_shift_const (x, code, result_mode, varop, count)
       if (complement_p)
        break;
 
-      /* Convert ROTATETRT to ROTATE.  */
+      /* Convert ROTATERT to ROTATE.  */
       if (code == ROTATERT)
        code = ROTATE, count = GET_MODE_BITSIZE (result_mode) - count;
 
-      /* Canonicalize LSHIFT to ASHIFT.  */
-      if (code == LSHIFT)
-       code = ASHIFT;
-
       /* We need to determine what mode we will do the shift in.  If the
-        shift is a ASHIFTRT or ROTATE, we must always do it in the mode it
-        was originally done in.  Otherwise, we can do it in MODE, the widest
-        mode encountered. */
-      shift_mode = (code == ASHIFTRT || code == ROTATE ? result_mode : mode);
+        shift is a right shift or a ROTATE, we must always do it in the mode
+        it was originally done in.  Otherwise, we can do it in MODE, the
+        widest mode encountered. */
+      shift_mode
+       = (code == ASHIFTRT || code == LSHIFTRT || code == ROTATE
+          ? result_mode : mode);
 
       /* Handle cases where the count is greater than the size of the mode
         minus 1.  For ASHIFT, use the size minus one as the count (this can
@@ -7574,16 +7761,15 @@ simplify_shift_const (x, code, result_mode, varop, count)
              && (tmode = mode_for_size (GET_MODE_BITSIZE (mode) - count,
                                         MODE_INT, 1)) != BLKmode)
            {
-#if BYTES_BIG_ENDIAN
-             new = gen_rtx (MEM, tmode, XEXP (varop, 0));
-#else
-             new = gen_rtx (MEM, tmode,
-                            plus_constant (XEXP (varop, 0),
-                                           count / BITS_PER_UNIT));
+             if (BYTES_BIG_ENDIAN)
+               new = gen_rtx (MEM, tmode, XEXP (varop, 0));
+             else
+               new = gen_rtx (MEM, tmode,
+                              plus_constant (XEXP (varop, 0),
+                                             count / BITS_PER_UNIT));
              RTX_UNCHANGING_P (new) = RTX_UNCHANGING_P (varop);
              MEM_VOLATILE_P (new) = MEM_VOLATILE_P (varop);
              MEM_IN_STRUCT_P (new) = MEM_IN_STRUCT_P (varop);
-#endif
              varop = gen_rtx_combine (code == ASHIFTRT ? SIGN_EXTEND
                                       : ZERO_EXTEND, mode, new);
              count = 0;
@@ -7601,14 +7787,15 @@ simplify_shift_const (x, code, result_mode, varop, count)
                                         MODE_INT, 1)) != BLKmode
              && tmode == GET_MODE (XEXP (varop, 0)))
            {
-#if BITS_BIG_ENDIAN
-             new = XEXP (varop, 0);
-#else
-             new = copy_rtx (XEXP (varop, 0));
-             SUBST (XEXP (new, 0), 
-                    plus_constant (XEXP (new, 0),
-                                   count / BITS_PER_UNIT));
-#endif
+             if (BITS_BIG_ENDIAN)
+               new = XEXP (varop, 0);
+             else
+               {
+                 new = copy_rtx (XEXP (varop, 0));
+                 SUBST (XEXP (new, 0), 
+                        plus_constant (XEXP (new, 0),
+                                       count / BITS_PER_UNIT));
+               }
 
              varop = gen_rtx_combine (code == ASHIFTRT ? SIGN_EXTEND
                                       : ZERO_EXTEND, mode, new);
@@ -7672,7 +7859,6 @@ simplify_shift_const (x, code, result_mode, varop, count)
 
        case LSHIFTRT:
        case ASHIFT:
-       case LSHIFT:
        case ROTATE:
          /* Here we have two nested shifts.  The result is usually the
             AND of a new shift with a mask.  We compute the result below.  */
@@ -7687,9 +7873,6 @@ simplify_shift_const (x, code, result_mode, varop, count)
              unsigned HOST_WIDE_INT mask;
              rtx mask_rtx;
 
-             if (first_code == LSHIFT)
-               first_code = ASHIFT;
-
              /* We have one common special case.  We can't do any merging if
                 the inner code is an ASHIFTRT of a smaller mode.  However, if
                 we have (ashift:M1 (subreg:M1 (ashiftrt:M2 FOO C1) 0) C2)
@@ -7741,7 +7924,7 @@ simplify_shift_const (x, code, result_mode, varop, count)
                 ASHIFTRT.
 
                 If the mode of this shift is not the mode of the outer shift,
-                we can't do this if either shift is ASHIFTRT or ROTATE.
+                we can't do this if either shift is a right shift or ROTATE.
 
                 Finally, we can't do any of these if the mode is too wide
                 unless the codes are the same.
@@ -7752,7 +7935,8 @@ simplify_shift_const (x, code, result_mode, varop, count)
              if (code == first_code)
                {
                  if (GET_MODE (varop) != result_mode
-                     && (code == ASHIFTRT || code == ROTATE))
+                     && (code == ASHIFTRT || code == LSHIFTRT
+                         || code == ROTATE))
                    break;
 
                  count += first_count;
@@ -7764,7 +7948,8 @@ simplify_shift_const (x, code, result_mode, varop, count)
                  || (code == ROTATE && first_code == ASHIFTRT)
                  || GET_MODE_BITSIZE (mode) > HOST_BITS_PER_WIDE_INT
                  || (GET_MODE (varop) != result_mode
-                     && (first_code == ASHIFTRT || first_code == ROTATE
+                     && (first_code == ASHIFTRT || first_code == LSHIFTRT
+                         || first_code == ROTATE
                          || code == ROTATE)))
                break;
 
@@ -7869,6 +8054,7 @@ simplify_shift_const (x, code, result_mode, varop, count)
              && (new = simplify_binary_operation (code, result_mode,
                                                   XEXP (varop, 1),
                                                   GEN_INT (count))) != 0
+             && GET_CODE(new) == CONST_INT
              && merge_outer_ops (&outer_op, &outer_const, GET_CODE (varop),
                                  INTVAL (new), result_mode, &complement_p))
            {
@@ -7893,11 +8079,11 @@ simplify_shift_const (x, code, result_mode, varop, count)
          break;
 
        case EQ:
-         /* convert (lshift (eq FOO 0) C) to (xor FOO 1) if STORE_FLAG_VALUE
+         /* convert (lshiftrt (eq FOO 0) C) to (xor FOO 1) if STORE_FLAG_VALUE
             says that the sign bit can be tested, FOO has mode MODE, C is
-            GET_MODE_BITSIZE (MODE) - 1, and FOO has only the low-order bit
-            may be nonzero.  */
-         if (code == LSHIFT
+            GET_MODE_BITSIZE (MODE) - 1, and FOO has only its low-order bit
+            that may be nonzero.  */
+         if (code == LSHIFTRT
              && XEXP (varop, 1) == const0_rtx
              && GET_MODE (XEXP (varop, 0)) == result_mode
              && count == GET_MODE_BITSIZE (result_mode) - 1
@@ -7988,6 +8174,7 @@ simplify_shift_const (x, code, result_mode, varop, count)
              && (new = simplify_binary_operation (ASHIFT, result_mode,
                                                   XEXP (varop, 1),
                                                   GEN_INT (count))) != 0
+             && GET_CODE(new) == CONST_INT
              && merge_outer_ops (&outer_op, &outer_const, PLUS,
                                  INTVAL (new), result_mode, &complement_p))
            {
@@ -8028,11 +8215,13 @@ simplify_shift_const (x, code, result_mode, varop, count)
     }
 
   /* We need to determine what mode to do the shift in.  If the shift is
-     a ASHIFTRT or ROTATE, we must always do it in the mode it was originally
-     done in.  Otherwise, we can do it in MODE, the widest mode encountered.
-     The code we care about is that of the shift that will actually be done,
-     not the shift that was originally requested.  */
-  shift_mode = (code == ASHIFTRT || code == ROTATE ? result_mode : mode);
+     a right shift or ROTATE, we must always do it in the mode it was
+     originally done in.  Otherwise, we can do it in MODE, the widest mode
+     encountered.  The code we care about is that of the shift that will
+     actually be done, not the shift that was originally requested.  */
+  shift_mode
+    = (code == ASHIFTRT || code == LSHIFTRT || code == ROTATE
+       ? result_mode : mode);
 
   /* We have now finished analyzing the shift.  The result should be
      a shift of type CODE with SHIFT_MODE shifting VAROP COUNT places.  If
@@ -8095,12 +8284,29 @@ simplify_shift_const (x, code, result_mode, varop, count)
   /* If COMPLEMENT_P is set, we have to complement X before doing the outer
      operation.  */
   if (complement_p)
-    x = gen_unary (NOT, result_mode, x);
+    x = gen_unary (NOT, result_mode, result_mode, x);
 
   if (outer_op != NIL)
     {
       if (GET_MODE_BITSIZE (result_mode) < HOST_BITS_PER_WIDE_INT)
-       outer_const &= GET_MODE_MASK (result_mode);
+       {
+         int width = GET_MODE_BITSIZE (result_mode);
+
+         outer_const &= GET_MODE_MASK (result_mode);
+
+         /* If this would be an entire word for the target, but is not for
+            the host, then sign-extend on the host so that the number will
+            look the same way on the host that it would on the target.
+
+            For example, when building a 64 bit alpha hosted 32 bit sparc
+            targeted compiler, then we want the 32 bit unsigned value -1 to be
+            represented as a 64 bit value -1, and not as 0x00000000ffffffff.
+            The later confuses the sparc backend.  */
+
+         if (BITS_PER_WORD < HOST_BITS_PER_WIDE_INT && BITS_PER_WORD == width
+             && (outer_const & ((HOST_WIDE_INT) 1 << (width - 1))))
+           outer_const |= ((HOST_WIDE_INT) (-1) << width);
+       }
 
       if (outer_op == AND)
        x = simplify_and_const_int (NULL_RTX, result_mode, x, outer_const);
@@ -8109,7 +8315,7 @@ simplify_shift_const (x, code, result_mode, varop, count)
           equivalent to a constant.  This should be rare.  */
        x = GEN_INT (outer_const);
       else if (GET_RTX_CLASS (outer_op) == '1')
-       x = gen_unary (outer_op, result_mode, x);
+       x = gen_unary (outer_op, result_mode, result_mode, x);
       else
        x = gen_binary (outer_op, result_mode, x, GEN_INT (outer_const));
     }
@@ -8127,14 +8333,18 @@ simplify_shift_const (x, code, result_mode, varop, count)
    PNOTES is a pointer to a location where any REG_UNUSED notes added for
    the CLOBBERs are placed.
 
+   PADDED_SCRATCHES is set to the number of (clobber (scratch)) patterns
+   we had to add.
+
    The value is the final insn code from the pattern ultimately matched,
    or -1.  */
 
 static int
-recog_for_combine (pnewpat, insn, pnotes)
+recog_for_combine (pnewpat, insn, pnotes, padded_scratches)
      rtx *pnewpat;
      rtx insn;
      rtx *pnotes;
+     int *padded_scratches;
 {
   register rtx pat = *pnewpat;
   int insn_code_number;
@@ -8142,6 +8352,8 @@ recog_for_combine (pnewpat, insn, pnotes)
   int i;
   rtx notes = 0;
 
+  *padded_scratches = 0;
+
   /* If PAT is a PARALLEL, check to see if it contains the CLOBBER
      we use to indicate that something didn't match.  If we find such a
      thing, force rejection.  */
@@ -8203,6 +8415,8 @@ recog_for_combine (pnewpat, insn, pnotes)
          if (GET_CODE (XEXP (XVECEXP (newpat, 0, i), 0)) == REG
              && ! reg_dead_at_p (XEXP (XVECEXP (newpat, 0, i), 0), insn))
            return -1;
+         else if (GET_CODE (XEXP (XVECEXP (newpat, 0, i), 0)) == SCRATCH)
+           (*padded_scratches)++;
          notes = gen_rtx (EXPR_LIST, REG_UNUSED,
                           XEXP (XVECEXP (newpat, 0, i), 0), notes);
        }
@@ -8257,6 +8471,14 @@ gen_lowpart_for_combine (mode, x)
     }
 
   result = gen_lowpart_common (mode, x);
+  if (result != 0
+      && GET_CODE (result) == SUBREG
+      && GET_CODE (SUBREG_REG (result)) == REG
+      && REGNO (SUBREG_REG (result)) >= FIRST_PSEUDO_REGISTER
+      && (GET_MODE_SIZE (GET_MODE (result))
+         != GET_MODE_SIZE (GET_MODE (SUBREG_REG (result)))))
+    reg_changes_size[REGNO (SUBREG_REG (result))] = 1;
+
   if (result)
     return result;
 
@@ -8276,16 +8498,16 @@ gen_lowpart_for_combine (mode, x)
       if (GET_MODE_SIZE (GET_MODE (x)) < GET_MODE_SIZE (mode))
        return gen_rtx (SUBREG, mode, x, 0);
 
-#if WORDS_BIG_ENDIAN
-      offset = (MAX (GET_MODE_SIZE (GET_MODE (x)), UNITS_PER_WORD)
-               - MAX (GET_MODE_SIZE (mode), UNITS_PER_WORD));
-#endif
-#if BYTES_BIG_ENDIAN
-      /* Adjust the address so that the address-after-the-data
-        is unchanged.  */
-      offset -= (MIN (UNITS_PER_WORD, GET_MODE_SIZE (mode))
-                - MIN (UNITS_PER_WORD, GET_MODE_SIZE (GET_MODE (x))));
-#endif
+      if (WORDS_BIG_ENDIAN)
+       offset = (MAX (GET_MODE_SIZE (GET_MODE (x)), UNITS_PER_WORD)
+                 - MAX (GET_MODE_SIZE (mode), UNITS_PER_WORD));
+      if (BYTES_BIG_ENDIAN)
+       {
+         /* Adjust the address so that the address-after-the-data is
+            unchanged.  */
+         offset -= (MIN (UNITS_PER_WORD, GET_MODE_SIZE (mode))
+                    - MIN (UNITS_PER_WORD, GET_MODE_SIZE (GET_MODE (x))));
+       }
       new = gen_rtx (MEM, mode, plus_constant (XEXP (x, 0), offset));
       RTX_UNCHANGING_P (new) = RTX_UNCHANGING_P (x);
       MEM_VOLATILE_P (new) = MEM_VOLATILE_P (x);
@@ -8441,12 +8663,12 @@ gen_binary (code, mode, op0, op1)
 }
 
 static rtx
-gen_unary (code, mode, op0)
+gen_unary (code, mode, op0_mode, op0)
      enum rtx_code code;
-     enum machine_mode mode;
+     enum machine_mode mode, op0_mode;
      rtx op0;
 {
-  rtx result = simplify_unary_operation (code, mode, op0, mode);
+  rtx result = simplify_unary_operation (code, mode, op0, op0_mode);
 
   if (result)
     return result;
@@ -8515,9 +8737,7 @@ simplify_comparison (code, pop0, pop1)
       if (GET_CODE (op0) == GET_CODE (op1)
          && GET_MODE_BITSIZE (GET_MODE (op0)) <= HOST_BITS_PER_WIDE_INT
          && ((GET_CODE (op0) == ROTATE && (code == NE || code == EQ))
-             || ((GET_CODE (op0) == LSHIFTRT
-                  || GET_CODE (op0) == ASHIFT
-                  || GET_CODE (op0) == LSHIFT)
+             || ((GET_CODE (op0) == LSHIFTRT || GET_CODE (op0) == ASHIFT)
                  && (code != GT && code != LT && code != GE && code != LE))
              || (GET_CODE (op0) == ASHIFTRT
                  && (code != GTU && code != LTU
@@ -8533,7 +8753,7 @@ simplify_comparison (code, pop0, pop1)
 
          if (GET_CODE (op0) == LSHIFTRT || GET_CODE (op0) == ASHIFTRT)
            mask &= (mask >> shift_count) << shift_count;
-         else if (GET_CODE (op0) == ASHIFT || GET_CODE (op0) == LSHIFT)
+         else if (GET_CODE (op0) == ASHIFT)
            mask = (mask & (mask << shift_count)) >> shift_count;
 
          if ((nonzero_bits (XEXP (op0, 0), mode) & ~ mask) == 0
@@ -8550,32 +8770,59 @@ simplify_comparison (code, pop0, pop1)
         and the operand's possibly nonzero bits are 0xffffff01; in that case
         if we only care about QImode, we don't need the AND).  This case
         occurs if the output mode of an scc insn is not SImode and
-        STORE_FLAG_VALUE == 1 (e.g., the 386).  */
+        STORE_FLAG_VALUE == 1 (e.g., the 386).
+
+        Similarly, check for a case where the AND's are ZERO_EXTEND
+        operations from some narrower mode even though a SUBREG is not
+        present.  */
 
       else if  (GET_CODE (op0) == AND && GET_CODE (op1) == AND
                && GET_CODE (XEXP (op0, 1)) == CONST_INT
-               && GET_CODE (XEXP (op1, 1)) == CONST_INT
-               && GET_CODE (XEXP (op0, 0)) == SUBREG
-               && GET_CODE (XEXP (op1, 0)) == SUBREG
-               && (GET_MODE_SIZE (GET_MODE (XEXP (op0, 0)))
-                   > GET_MODE_SIZE (GET_MODE (SUBREG_REG (XEXP (op0, 0)))))
-               && (GET_MODE (SUBREG_REG (XEXP (op0, 0)))
-                   == GET_MODE (SUBREG_REG (XEXP (op1, 0))))
-               && (GET_MODE_BITSIZE (GET_MODE (SUBREG_REG (XEXP (op0, 0))))
-                   <= HOST_BITS_PER_WIDE_INT)
-               && (nonzero_bits (SUBREG_REG (XEXP (op0, 0)),
-                                     GET_MODE (SUBREG_REG (XEXP (op0, 0))))
-                   & ~ INTVAL (XEXP (op0, 1))) == 0
-               && (nonzero_bits (SUBREG_REG (XEXP (op1, 0)),
-                                     GET_MODE (SUBREG_REG (XEXP (op1, 0))))
-                   & ~ INTVAL (XEXP (op1, 1))) == 0)
+               && GET_CODE (XEXP (op1, 1)) == CONST_INT)
        {
-         op0 = SUBREG_REG (XEXP (op0, 0));
-         op1 = SUBREG_REG (XEXP (op1, 0));
+         rtx inner_op0 = XEXP (op0, 0);
+         rtx inner_op1 = XEXP (op1, 0);
+         HOST_WIDE_INT c0 = INTVAL (XEXP (op0, 1));
+         HOST_WIDE_INT c1 = INTVAL (XEXP (op1, 1));
+         int changed = 0;
+               
+         if (GET_CODE (inner_op0) == SUBREG && GET_CODE (inner_op1) == SUBREG
+             && (GET_MODE_SIZE (GET_MODE (inner_op0))
+                 > GET_MODE_SIZE (GET_MODE (SUBREG_REG (inner_op0))))
+             && (GET_MODE (SUBREG_REG (inner_op0))
+                 == GET_MODE (SUBREG_REG (inner_op1)))
+             && (GET_MODE_BITSIZE (GET_MODE (SUBREG_REG (op0)))
+                 <= HOST_BITS_PER_WIDE_INT)
+             && (0 == (~c0) & nonzero_bits (SUBREG_REG (inner_op0),
+                                            GET_MODE (SUBREG_REG (op0))))
+             && (0 == (~c1) & nonzero_bits (SUBREG_REG (inner_op1),
+                                            GET_MODE (SUBREG_REG (inner_op1)))))
+           {
+             op0 = SUBREG_REG (inner_op0);
+             op1 = SUBREG_REG (inner_op1);
 
-         /* the resulting comparison is always unsigned since we masked off
-            the original sign bit. */
-         code = unsigned_condition (code);
+             /* The resulting comparison is always unsigned since we masked
+                off the original sign bit. */
+             code = unsigned_condition (code);
+
+             changed = 1;
+           }
+
+         else if (c0 == c1)
+           for (tmode = GET_CLASS_NARROWEST_MODE
+                (GET_MODE_CLASS (GET_MODE (op0)));
+                tmode != GET_MODE (op0); tmode = GET_MODE_WIDER_MODE (tmode))
+             if (c0 == GET_MODE_MASK (tmode))
+               {
+                 op0 = gen_lowpart_for_combine (tmode, inner_op0);
+                 op1 = gen_lowpart_for_combine (tmode, inner_op1);
+                 code = unsigned_condition (code);
+                 changed = 1;
+                 break;
+               }
+
+         if (! changed)
+           break;
        }
 
       /* If both operands are NOT, we can strip off the outer operation
@@ -8771,6 +9018,7 @@ simplify_comparison (code, pop0, pop1)
            {
              const_op = 0, op1 = const0_rtx;
              code = LT;
+             break;
            }
          else
            break;
@@ -8819,15 +9067,20 @@ simplify_comparison (code, pop0, pop1)
             do this if bit endian and we don't have an extzv since we then
             can't know what mode to use for the endianness adjustment.  */
 
-#if ! BITS_BIG_ENDIAN || defined (HAVE_extzv)
          if (GET_CODE (XEXP (op0, 0)) == CONST_INT
              && XEXP (op0, 1) == const1_rtx
              && equality_comparison_p && const_op == 0
-             && (i = exact_log2 (INTVAL (XEXP (op0, 0)))) >= 0)
+             && (i = exact_log2 (INTVAL (XEXP (op0, 0)))) >= 0
+             && (! BITS_BIG_ENDIAN
+#ifdef HAVE_extzv
+                 || HAVE_extzv
+#endif
+                 ))
            {
-#if BITS_BIG_ENDIAN
-             i = (GET_MODE_BITSIZE
-                  (insn_operand_mode[(int) CODE_FOR_extzv][1]) - 1 - i);
+#ifdef HAVE_extzv
+             if (BITS_BIG_ENDIAN)
+               i = (GET_MODE_BITSIZE
+                    (insn_operand_mode[(int) CODE_FOR_extzv][1]) - 1 - i);
 #endif
 
              op0 = XEXP (op0, 2);
@@ -8838,7 +9091,6 @@ simplify_comparison (code, pop0, pop1)
              code = reverse_condition (code);
              continue;
            }
-#endif
 
          /* ... fall through ... */
 
@@ -8967,7 +9219,7 @@ simplify_comparison (code, pop0, pop1)
 
        case SUBREG:
          /* Check for the case where we are comparing A - C1 with C2,
-            both constants are smaller than 1/2 the maxium positive
+            both constants are smaller than 1/2 the maximum positive
             value in MODE, and the comparison is equality or unsigned.
             In that case, if A is either zero-extended to MODE or has
             sufficient sign bits so that the high-order bit in MODE
@@ -9143,8 +9395,7 @@ simplify_comparison (code, pop0, pop1)
          /* Convert (and (xshift 1 X) Y) to (and (lshiftrt Y X) 1).  This
             will be converted to a ZERO_EXTRACT later.  */
          if (const_op == 0 && equality_comparison_p
-             && (GET_CODE (XEXP (op0, 0)) == ASHIFT
-                 || GET_CODE (XEXP (op0, 0)) == LSHIFT)
+             && GET_CODE (XEXP (op0, 0)) == ASHIFT
              && XEXP (XEXP (op0, 0), 0) == const1_rtx)
            {
              op0 = simplify_and_const_int
@@ -9211,8 +9462,7 @@ simplify_comparison (code, pop0, pop1)
          break;
 
        case ASHIFT:
-       case LSHIFT:
-         /* If we have (compare (xshift FOO N) (const_int C)) and
+         /* If we have (compare (ashift FOO N) (const_int C)) and
             the high order N bits of FOO (N+1 if an inequality comparison)
             are known to be zero, we can do this by comparing FOO with C
             shifted right N bits so long as the low-order N bits of C are
@@ -9379,15 +9629,13 @@ simplify_comparison (code, pop0, pop1)
          /* If the only nonzero bits in OP0 and OP1 are those in the
             narrower mode and this is an equality or unsigned comparison,
             we can use the wider mode.  Similarly for sign-extended
-            values and equality or signed comparisons.  */
+            values, in which case it is true for all comparisons.  */
          if (((code == EQ || code == NE
                || code == GEU || code == GTU || code == LEU || code == LTU)
               && (nonzero_bits (op0, tmode) & ~ GET_MODE_MASK (mode)) == 0
               && (nonzero_bits (op1, tmode) & ~ GET_MODE_MASK (mode)) == 0)
-             || ((code == EQ || code == NE
-                  || code == GE || code == GT || code == LE || code == LT)
-                 && (num_sign_bit_copies (op0, tmode)
-                     > GET_MODE_BITSIZE (tmode) - GET_MODE_BITSIZE (mode))
+             || ((num_sign_bit_copies (op0, tmode)
+                  > GET_MODE_BITSIZE (tmode) - GET_MODE_BITSIZE (mode))
                  && (num_sign_bit_copies (op1, tmode)
                      > GET_MODE_BITSIZE (tmode) - GET_MODE_BITSIZE (mode))))
            {
@@ -9411,6 +9659,12 @@ simplify_comparison (code, pop0, pop1)
            }
        }
 
+#ifdef CANONICALIZE_COMPARISON
+  /* If this machine only supports a subset of valid comparisons, see if we
+     can convert an unsupported one into a supported one.  */
+  CANONICALIZE_COMPARISON (code, op0, op1);
+#endif
+
   *pop0 = op0;
   *pop1 = op1;
 
@@ -9586,6 +9840,9 @@ static void
 record_dead_and_set_regs_1 (dest, setter)
      rtx dest, setter;
 {
+  if (GET_CODE (dest) == SUBREG)
+    dest = SUBREG_REG (dest);
+
   if (GET_CODE (dest) == REG)
     {
       /* If we are setting the whole register, we know its value.  Otherwise
@@ -9596,6 +9853,7 @@ record_dead_and_set_regs_1 (dest, setter)
       else if (GET_CODE (setter) == SET
               && GET_CODE (SET_DEST (setter)) == SUBREG
               && SUBREG_REG (SET_DEST (setter)) == dest
+              && GET_MODE_BITSIZE (GET_MODE (dest)) <= BITS_PER_WORD
               && subreg_lowpart_p (SET_DEST (setter)))
        record_value_for_reg (dest, record_dead_insn,
                              gen_lowpart_for_combine (GET_MODE (dest),
@@ -9751,24 +10009,36 @@ get_last_value (x)
          && reg_last_set_label[regno] != label_tick))
     return 0;
 
-  /* If the value was set in a later insn that the ones we are processing,
+  /* If the value was set in a later insn than the ones we are processing,
      we can't use it even if the register was only set once, but make a quick
      check to see if the previous insn set it to something.  This is commonly
-     the case when the same pseudo is used by repeated insns.  */
+     the case when the same pseudo is used by repeated insns.
+
+     This does not work if there exists an instruction which is temporarily
+     not on the insn chain.  */
 
   if (INSN_CUID (reg_last_set[regno]) >= subst_low_cuid)
     {
       rtx insn, set;
 
-      /* If there is an insn that is supposed to be immediately
-        in front of subst_insn, use it.  */
-      if (subst_prev_insn != 0)
-       insn = subst_prev_insn;
-      else
-       for (insn = prev_nonnote_insn (subst_insn);
-            insn && INSN_CUID (insn) >= subst_low_cuid;
-            insn = prev_nonnote_insn (insn))
-         ;
+      /* We can not do anything useful in this case, because there is
+        an instruction which is not on the insn chain.  */
+      if (subst_prev_insn)
+       return 0;
+
+      /* Skip over USE insns.  They are not useful here, and they may have
+        been made by combine, in which case they do not have a INSN_CUID
+        value.  We can't use prev_real_insn, because that would incorrectly
+        take us backwards across labels.  Skip over BARRIERs also, since
+        they could have been made by combine.  If we see one, we must be
+        optimizing dead code, so it doesn't matter what we do.  */
+      for (insn = prev_nonnote_insn (subst_insn);
+          insn && ((GET_CODE (insn) == INSN
+                    && GET_CODE (PATTERN (insn)) == USE)
+                   || GET_CODE (insn) == BARRIER
+                   || INSN_CUID (insn) >= subst_low_cuid);
+          insn = prev_nonnote_insn (insn))
+       ;
 
       if (insn
          && (set = single_set (insn)) != 0
@@ -9777,7 +10047,7 @@ get_last_value (x)
          value = SET_SRC (set);
 
          /* Make sure that VALUE doesn't reference X.  Replace any
-            expliit references with a CLOBBER.  If there are any remaining
+            explicit references with a CLOBBER.  If there are any remaining
             references (rare), don't use the value.  */
 
          if (reg_mentioned_p (x, value))
@@ -9865,7 +10135,7 @@ static int reg_dead_flag;
 
 /* Function called via note_stores from reg_dead_at_p.
 
-   If DEST is within [reg_dead_rengno, reg_dead_endregno), set 
+   If DEST is within [reg_dead_regno, reg_dead_endregno), set 
    reg_dead_flag to 1 if X is a CLOBBER and to -1 it is a SET.  */
 
 static void
@@ -9920,7 +10190,7 @@ reg_dead_at_p (reg, insn)
 
   /* Scan backwards until we find a REG_DEAD note, SET, CLOBBER, label, or
      beginning of function.  */
-  for (; insn && GET_CODE (insn) != CODE_LABEL;
+  for (; insn && GET_CODE (insn) != CODE_LABEL && GET_CODE (insn) != BARRIER;
        insn = prev_nonnote_insn (insn))
     {
       note_stores (PATTERN (insn), reg_dead_at_p_1);
@@ -10095,9 +10365,22 @@ move_deaths (x, from_cuid, to_insn, pnotes)
     {
       register int regno = REGNO (x);
       register rtx where_dead = reg_last_death[regno];
-
-      if (where_dead && INSN_CUID (where_dead) >= from_cuid
-         && INSN_CUID (where_dead) < INSN_CUID (to_insn))
+      register rtx before_dead, after_dead;
+
+      /* WHERE_DEAD could be a USE insn made by combine, so first we
+        make sure that we have insns with valid INSN_CUID values.  */
+      before_dead = where_dead;
+      while (before_dead && INSN_UID (before_dead) > max_uid_cuid)
+       before_dead = PREV_INSN (before_dead);
+      after_dead = where_dead;
+      while (after_dead && INSN_UID (after_dead) > max_uid_cuid)
+       after_dead = NEXT_INSN (after_dead);
+
+      if (before_dead && after_dead
+         && INSN_CUID (before_dead) >= from_cuid
+         && (INSN_CUID (after_dead) < INSN_CUID (to_insn)
+             || (where_dead != after_dead
+                 && INSN_CUID (after_dead) == INSN_CUID (to_insn))))
        {
          rtx note = remove_death (regno, where_dead);
 
@@ -10125,9 +10408,24 @@ move_deaths (x, from_cuid, to_insn, pnotes)
                if (i < regno || i >= ourend)
                  REG_NOTES (where_dead)
                    = gen_rtx (EXPR_LIST, REG_DEAD,
-                              gen_rtx (REG, word_mode, i),
+                              gen_rtx (REG, reg_raw_mode[i], i),
                               REG_NOTES (where_dead));
            }
+         /* If we didn't find any note, and we have a multi-reg hard
+            register, then to be safe we must check for REG_DEAD notes
+            for each register other than the first.  They could have
+            their own REG_DEAD notes lying around.  */
+         else if (note == 0 && regno < FIRST_PSEUDO_REGISTER
+                  && HARD_REGNO_NREGS (regno, GET_MODE (x)) > 1)
+           {
+             int ourend = regno + HARD_REGNO_NREGS (regno, GET_MODE (x));
+             int i;
+             rtx oldnotes = 0;
+
+             for (i = regno + 1; i < ourend; i++)
+               move_deaths (gen_rtx (REG, reg_raw_mode[i], i),
+                            from_cuid, to_insn, &oldnotes);
+           }
 
          if (note != 0 && GET_MODE (XEXP (note, 0)) == GET_MODE (x))
            {
@@ -10281,10 +10579,7 @@ distribute_notes (notes, from_insn, i3, i2, elim_i2, elim_i1)
       switch (REG_NOTE_KIND (note))
        {
        case REG_UNUSED:
-         /* If this note is from any insn other than i3, then we have no
-            use for it, and must ignore it.
-
-            Any clobbers for i3 may still exist, and so we must process
+         /* Any clobbers for i3 may still exist, and so we must process
             REG_UNUSED notes from that insn.
 
             Any clobbers from i2 or i1 can only exist if they were added by
@@ -10294,14 +10589,18 @@ distribute_notes (notes, from_insn, i3, i2, elim_i2, elim_i1)
             if it is for the same register as the original i3 dest.
             In that case, we will notice that the register is set in i3,
             and then add a REG_UNUSED note for the destination of i3, which
-            is wrong.  */
-         if (from_insn != i3)
-           break;
+            is wrong.  However, it is possible to have REG_UNUSED notes from
+            i2 or i1 for register which were both used and clobbered, so
+            we keep notes from i2 or i1 if they will turn into REG_DEAD
+            notes.  */
 
          /* If this register is set or clobbered in I3, put the note there
             unless there is one already.  */
-         else if (reg_set_p (XEXP (note, 0), PATTERN (i3)))
+         if (reg_set_p (XEXP (note, 0), PATTERN (i3)))
            {
+             if (from_insn != i3)
+               break;
+
              if (! (GET_CODE (XEXP (note, 0)) == REG
                     ? find_regno_note (i3, REG_UNUSED, REGNO (XEXP (note, 0)))
                     : find_reg_note (i3, REG_UNUSED, XEXP (note, 0))))
@@ -10404,7 +10703,11 @@ distribute_notes (notes, from_insn, i3, i2, elim_i2, elim_i1)
             In both cases, we must search to see if we can find a previous
             use of A and put the death note there.  */
 
-         if (reg_referenced_p (XEXP (note, 0), PATTERN (i3)))
+         if (from_insn
+             && GET_CODE (from_insn) == CALL_INSN
+              && find_reg_fusage (from_insn, USE, XEXP (note, 0)))
+           place = from_insn;
+         else if (reg_referenced_p (XEXP (note, 0), PATTERN (i3)))
            place = i3;
          else if (i2 != 0 && next_nonnote_insn (i2) == i3
                   && reg_referenced_p (XEXP (note, 0), PATTERN (i2)))
@@ -10426,57 +10729,97 @@ distribute_notes (notes, from_insn, i3, i2, elim_i2, elim_i1)
            reg_n_refs[REGNO (XEXP (note, 0))] = 3;
 
          if (place == 0)
-           for (tem = prev_nonnote_insn (i3);
-                tem && (GET_CODE (tem) == INSN
-                        || GET_CODE (tem) == CALL_INSN);
-                tem = prev_nonnote_insn (tem))
-             {
-               /* If the register is being set at TEM, see if that is all
-                  TEM is doing.  If so, delete TEM.  Otherwise, make this
-                  into a REG_UNUSED note instead.  */
-               if (reg_set_p (XEXP (note, 0), PATTERN (tem)))
-                 {
-                   rtx set = single_set (tem);
+           {
+             for (tem = prev_nonnote_insn (i3);
+                  place == 0 && tem
+                  && (GET_CODE (tem) == INSN || GET_CODE (tem) == CALL_INSN);
+                  tem = prev_nonnote_insn (tem))
+               {
+                 /* If the register is being set at TEM, see if that is all
+                    TEM is doing.  If so, delete TEM.  Otherwise, make this
+                    into a REG_UNUSED note instead.  */
+                 if (reg_set_p (XEXP (note, 0), PATTERN (tem)))
+                   {
+                     rtx set = single_set (tem);
 
-                   /* Verify that it was the set, and not a clobber that
-                      modified the register.  */
+                     /* Verify that it was the set, and not a clobber that
+                        modified the register.  */
 
-                   if (set != 0 && ! side_effects_p (SET_SRC (set))
-                       && rtx_equal_p (XEXP (note, 0), SET_DEST (set)))
-                     {
-                       /* Move the notes and links of TEM elsewhere.
-                          This might delete other dead insns recursively. 
-                          First set the pattern to something that won't use
-                          any register.  */
+                     if (set != 0 && ! side_effects_p (SET_SRC (set))
+                         && (rtx_equal_p (XEXP (note, 0), SET_DEST (set))
+                             || (GET_CODE (SET_DEST (set)) == SUBREG
+                                 && rtx_equal_p (XEXP (note, 0),
+                                                 XEXP (SET_DEST (set), 0)))))
+                       {
+                         /* Move the notes and links of TEM elsewhere.
+                            This might delete other dead insns recursively. 
+                            First set the pattern to something that won't use
+                            any register.  */
 
-                       PATTERN (tem) = pc_rtx;
+                         PATTERN (tem) = pc_rtx;
 
-                       distribute_notes (REG_NOTES (tem), tem, tem,
-                                         NULL_RTX, NULL_RTX, NULL_RTX);
-                       distribute_links (LOG_LINKS (tem));
+                         distribute_notes (REG_NOTES (tem), tem, tem,
+                                           NULL_RTX, NULL_RTX, NULL_RTX);
+                         distribute_links (LOG_LINKS (tem));
 
-                       PUT_CODE (tem, NOTE);
-                       NOTE_LINE_NUMBER (tem) = NOTE_INSN_DELETED;
-                       NOTE_SOURCE_FILE (tem) = 0;
-                     }
-                   else
-                     {
-                       PUT_REG_NOTE_KIND (note, REG_UNUSED);
-
-                       /*  If there isn't already a REG_UNUSED note, put one
-                           here.  */
-                       if (! find_regno_note (tem, REG_UNUSED,
-                                              REGNO (XEXP (note, 0))))
-                         place = tem;
-                       break;
+                         PUT_CODE (tem, NOTE);
+                         NOTE_LINE_NUMBER (tem) = NOTE_INSN_DELETED;
+                         NOTE_SOURCE_FILE (tem) = 0;
+                       }
+                     else
+                       {
+                         PUT_REG_NOTE_KIND (note, REG_UNUSED);
+                         
+                         /*  If there isn't already a REG_UNUSED note, put one
+                             here.  */
+                         if (! find_regno_note (tem, REG_UNUSED,
+                                                REGNO (XEXP (note, 0))))
+                           place = tem;
+                         break;
                      }
                  }
-               else if (reg_referenced_p (XEXP (note, 0), PATTERN (tem)))
+               else if (reg_referenced_p (XEXP (note, 0), PATTERN (tem))
+                        || (GET_CODE (tem) == CALL_INSN
+                            && find_reg_fusage (tem, USE, XEXP (note, 0))))
                  {
                    place = tem;
+
+                   /* If we are doing a 3->2 combination, and we have a
+                      register which formerly died in i3 and was not used
+                      by i2, which now no longer dies in i3 and is used in
+                      i2 but does not die in i2, and place is between i2
+                      and i3, then we may need to move a link from place to
+                      i2.  */
+                   if (i2 && INSN_UID (place) <= max_uid_cuid
+                       && INSN_CUID (place) > INSN_CUID (i2)
+                       && from_insn && INSN_CUID (from_insn) > INSN_CUID (i2)
+                       && reg_referenced_p (XEXP (note, 0), PATTERN (i2)))
+                     {
+                       rtx links = LOG_LINKS (place);
+                       LOG_LINKS (place) = 0;
+                       distribute_links (links);
+                     }
                    break;
                  }
-             }
+               }
+             
+             /* If we haven't found an insn for the death note and it
+                is still a REG_DEAD note, but we have hit a CODE_LABEL,
+                insert a USE insn for the register at that label and
+                put the death node there.  This prevents problems with
+                call-state tracking in caller-save.c.  */
+             if (REG_NOTE_KIND (note) == REG_DEAD && place == 0 && tem != 0)
+               {
+                 place
+                   = emit_insn_after (gen_rtx (USE, VOIDmode, XEXP (note, 0)),
+                                      tem);
+
+                 /* If this insn was emitted between blocks, then update
+                    basic_block_head of the current block to include it.  */
+                 if (basic_block_end[this_basic_block - 1] == tem)
+                   basic_block_head[this_basic_block] = place;
+               }
+           }
 
          /* If the register is set or already dead at PLACE, we needn't do
             anything with this note if it is still a REG_DEAD note.  
@@ -10524,9 +10867,10 @@ distribute_notes (notes, from_insn, i3, i2, elim_i2, elim_i1)
                  int i;
 
                  for (i = regno; i < endregno; i++)
-                   if (! refers_to_regno_p (i, i + 1, PATTERN (place), 0))
+                   if (! refers_to_regno_p (i, i + 1, PATTERN (place), 0)
+                       && ! find_regno_fusage (place, USE, i))
                      {
-                       rtx piece = gen_rtx (REG, word_mode, i);
+                       rtx piece = gen_rtx (REG, reg_raw_mode[i], i);
                        rtx p;
 
                        /* See if we already placed a USE note for this
@@ -10573,9 +10917,11 @@ distribute_notes (notes, from_insn, i3, i2, elim_i2, elim_i1)
 
                      for (i = regno; i < endregno; i++)
                        {
-                         rtx piece = gen_rtx (REG, word_mode, i);
+                         rtx piece = gen_rtx (REG, reg_raw_mode[i], i);
 
-                         if (reg_referenced_p (piece, PATTERN (place))
+                         if ((reg_referenced_p (piece, PATTERN (place))
+                              || (GET_CODE (place) == CALL_INSN
+                                  && find_reg_fusage (place, USE, piece)))
                              && ! dead_or_set_p (place, piece)
                              && ! reg_bitfield_target_p (piece,
                                                          PATTERN (place)))
@@ -10678,6 +11024,12 @@ distribute_links (links)
              place = insn;
            break;
          }
+       else if (GET_CODE (insn) == CALL_INSN
+             && find_reg_fusage (insn, USE, reg))
+         {
+           place = insn;
+           break;
+         }
 
       /* If we found a place to put the link, place it there unless there
         is already a link to the same insn as LINK at that point.  */