diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 1672806b59abe82074d14ac74d21771ef8de89b3..fc8466f020b1ac87683a7a7031e6c0d69ae9b724 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,16 @@
+2005-09-10  Richard Earnshaw  <richard.earnshaw@arm.com>
+
+	* arm.c (arm_gen_rotated_half_load): Delete.
+	(vfp_emit_fstmx, arm_set_return_address): Use gen_frame_mem.
+	(emit_multi_reg_push, emit_sfm, arm_expand_prologue)
+	(thumb_set_return_address): Likewise.
+	(thumb_load_double_from_address): Use adjust_address.
+	* arm.md (splits calling arm_gen_rotated_half_load): Delete.
+	(extendhsisi2_mem, movhi_bytes): Use change_address.
+	(movhi): Use widen_memory_access.
+	(reload_out_df): Use replace_equiv_address.
+	* arm-protos.h (arm_gen_rotated_half_load): Delete prototype.
+
 2005-09-09  Richard Henderson  <rth@redhat.com>
 
 	PR debug/20998
diff --git a/gcc/config/arm/arm-protos.h b/gcc/config/arm/arm-protos.h
index c7ec642c72806b4363c22924890e2c81465ac5ae..b8913a1cf595b74b837a8cf92bd3d53889325221 100644
--- a/gcc/config/arm/arm-protos.h
+++ b/gcc/config/arm/arm-protos.h
@@ -87,7 +87,6 @@ extern rtx arm_gen_load_multiple (int, int, rtx, int, int,
 extern rtx arm_gen_store_multiple (int, int, rtx, int, int,
 				   rtx, HOST_WIDE_INT *);
 extern int arm_gen_movmemqi (rtx *);
-extern rtx arm_gen_rotated_half_load (rtx);
 extern enum machine_mode arm_select_cc_mode (RTX_CODE, rtx, rtx);
 extern enum machine_mode arm_select_dominance_cc_mode (rtx, rtx,
 						       HOST_WIDE_INT);
diff --git a/gcc/config/arm/arm.c b/gcc/config/arm/arm.c
index 7df3aba1c23c0c24097a66734e05dcdfb8df5d6e..60acf36d1f1ebe4374f6b9f5539545de3b405d47 100644
--- a/gcc/config/arm/arm.c
+++ b/gcc/config/arm/arm.c
@@ -6117,30 +6117,6 @@ arm_gen_movmemqi (rtx *operands)
    into the top 16 bits of the word.  We can assume that the address is
    known to be alignable and of the form reg, or plus (reg, const).  */
 
-rtx
-arm_gen_rotated_half_load (rtx memref)
-{
-  HOST_WIDE_INT offset = 0;
-  rtx base = XEXP (memref, 0);
-
-  if (GET_CODE (base) == PLUS)
-    {
-      offset = INTVAL (XEXP (base, 1));
-      base = XEXP (base, 0);
-    }
-
-  /* If we aren't allowed to generate unaligned addresses, then fail.  */
-  if ((BYTES_BIG_ENDIAN ? 1 : 0) ^ ((offset & 2) == 0))
-    return NULL;
-
-  base = gen_rtx_MEM (SImode, plus_constant (base, offset & ~2));
-
-  if ((BYTES_BIG_ENDIAN ? 1 : 0) ^ ((offset & 2) == 2))
-    return base;
-
-  return gen_rtx_ROTATE (SImode, base, GEN_INT (16));
-}
-
 /* Select a dominance comparison mode if possible for a test of the general
    form (OP (COND_OR (X) (Y)) (const_int 0)).  We support three forms.
    COND_OR == DOM_CC_X_AND_Y => (X && Y)
@@ -8128,8 +8104,9 @@ vfp_emit_fstmx (int base_reg, int count)
 
   XVECEXP (par, 0, 0)
     = gen_rtx_SET (VOIDmode,
-		   gen_rtx_MEM (BLKmode,
-				gen_rtx_PRE_DEC (BLKmode, stack_pointer_rtx)),
+		   gen_frame_mem (BLKmode,
+				  gen_rtx_PRE_DEC (BLKmode,
+						   stack_pointer_rtx)),
 		   gen_rtx_UNSPEC (BLKmode,
 				   gen_rtvec (1, reg),
 				   UNSPEC_PUSH_MULT));
@@ -8141,7 +8118,7 @@ vfp_emit_fstmx (int base_reg, int count)
   XVECEXP (dwarf, 0, 0) = tmp;
 
   tmp = gen_rtx_SET (VOIDmode,
-		     gen_rtx_MEM (DFmode, stack_pointer_rtx),
+		     gen_frame_mem (DFmode, stack_pointer_rtx),
 		     reg);
   RTX_FRAME_RELATED_P (tmp) = 1;
   XVECEXP (dwarf, 0, 1) = tmp;
@@ -8153,10 +8130,10 @@ vfp_emit_fstmx (int base_reg, int count)
       XVECEXP (par, 0, i) = gen_rtx_USE (VOIDmode, reg);
 
       tmp = gen_rtx_SET (VOIDmode,
-			 gen_rtx_MEM (DFmode,
-				      gen_rtx_PLUS (SImode,
-						    stack_pointer_rtx,
-						    GEN_INT (i * 8))),
+			 gen_frame_mem (DFmode,
+					gen_rtx_PLUS (SImode,
+						      stack_pointer_rtx,
+						      GEN_INT (i * 8))),
 			 reg);
       RTX_FRAME_RELATED_P (tmp) = 1;
       XVECEXP (dwarf, 0, i + 1) = tmp;
@@ -9851,9 +9828,9 @@ emit_multi_reg_push (unsigned long mask)
 
 	  XVECEXP (par, 0, 0)
 	    = gen_rtx_SET (VOIDmode,
-			   gen_rtx_MEM (BLKmode,
-					gen_rtx_PRE_DEC (BLKmode,
-							 stack_pointer_rtx)),
+			   gen_frame_mem (BLKmode,
+					  gen_rtx_PRE_DEC (BLKmode,
+							   stack_pointer_rtx)),
 			   gen_rtx_UNSPEC (BLKmode,
 					   gen_rtvec (1, reg),
 					   UNSPEC_PUSH_MULT));
@@ -9861,7 +9838,7 @@ emit_multi_reg_push (unsigned long mask)
 	  if (i != PC_REGNUM)
 	    {
 	      tmp = gen_rtx_SET (VOIDmode,
-				 gen_rtx_MEM (SImode, stack_pointer_rtx),
+				 gen_frame_mem (SImode, stack_pointer_rtx),
 				 reg);
 	      RTX_FRAME_RELATED_P (tmp) = 1;
 	      XVECEXP (dwarf, 0, dwarf_par_index) = tmp;
@@ -9882,11 +9859,12 @@ emit_multi_reg_push (unsigned long mask)
 
 	  if (i != PC_REGNUM)
 	    {
-	      tmp = gen_rtx_SET (VOIDmode,
-				 gen_rtx_MEM (SImode,
+	      tmp
+		= gen_rtx_SET (VOIDmode,
+			       gen_frame_mem (SImode,
 					      plus_constant (stack_pointer_rtx,
 							     4 * j)),
-				 reg);
+			       reg);
 	      RTX_FRAME_RELATED_P (tmp) = 1;
 	      XVECEXP (dwarf, 0, dwarf_par_index++) = tmp;
 	    }
@@ -9939,13 +9917,14 @@ emit_sfm (int base_reg, int count)
 
   XVECEXP (par, 0, 0)
     = gen_rtx_SET (VOIDmode,
-		   gen_rtx_MEM (BLKmode,
-				gen_rtx_PRE_DEC (BLKmode, stack_pointer_rtx)),
+		   gen_frame_mem (BLKmode,
+				  gen_rtx_PRE_DEC (BLKmode,
+						   stack_pointer_rtx)),
 		   gen_rtx_UNSPEC (BLKmode,
 				   gen_rtvec (1, reg),
 				   UNSPEC_PUSH_MULT));
   tmp = gen_rtx_SET (VOIDmode,
-		     gen_rtx_MEM (XFmode, stack_pointer_rtx), reg);
+		     gen_frame_mem (XFmode, stack_pointer_rtx), reg);
   RTX_FRAME_RELATED_P (tmp) = 1;
   XVECEXP (dwarf, 0, 1) = tmp;
 
@@ -9955,9 +9934,9 @@ emit_sfm (int base_reg, int count)
       XVECEXP (par, 0, i) = gen_rtx_USE (VOIDmode, reg);
 
       tmp = gen_rtx_SET (VOIDmode,
-			 gen_rtx_MEM (XFmode,
-				      plus_constant (stack_pointer_rtx,
-						     i * 12)),
+			 gen_frame_mem (XFmode,
+					plus_constant (stack_pointer_rtx,
+						       i * 12)),
 			 reg);
       RTX_FRAME_RELATED_P (tmp) = 1;
       XVECEXP (dwarf, 0, i + 1) = tmp;
@@ -10309,7 +10288,7 @@ arm_expand_prologue (void)
 	    {
 	      rtx dwarf;
 	      insn = gen_rtx_PRE_DEC (SImode, stack_pointer_rtx);
-	      insn = gen_rtx_MEM (SImode, insn);
+	      insn = gen_frame_mem (SImode, insn);
 	      insn = gen_rtx_SET (VOIDmode, insn, ip_rtx);
 	      insn = emit_insn (insn);
 
@@ -10398,7 +10377,7 @@ arm_expand_prologue (void)
       if (regs_ever_live[reg] && ! call_used_regs [reg])
 	{
 	  insn = gen_rtx_PRE_DEC (V2SImode, stack_pointer_rtx);
-	  insn = gen_rtx_MEM (V2SImode, insn);
+	  insn = gen_frame_mem (V2SImode, insn);
 	  insn = emit_insn (gen_rtx_SET (VOIDmode, insn,
 					 gen_rtx_REG (V2SImode, reg)));
 	  RTX_FRAME_RELATED_P (insn) = 1;
@@ -10417,7 +10396,7 @@ arm_expand_prologue (void)
 	    if (regs_ever_live[reg] && !call_used_regs[reg])
 	      {
 		insn = gen_rtx_PRE_DEC (XFmode, stack_pointer_rtx);
-		insn = gen_rtx_MEM (XFmode, insn);
+		insn = gen_frame_mem (XFmode, insn);
 		insn = emit_insn (gen_rtx_SET (VOIDmode, insn,
 					       gen_rtx_REG (XFmode, reg)));
 		RTX_FRAME_RELATED_P (insn) = 1;
@@ -10497,7 +10476,7 @@ arm_expand_prologue (void)
 	    {
 	      insn = gen_rtx_PLUS (SImode, hard_frame_pointer_rtx,
 				   GEN_INT (4));
-	      insn = gen_rtx_MEM (SImode, insn);
+	      insn = gen_frame_mem (SImode, insn);
 	    }
 
 	  emit_insn (gen_rtx_SET (SImode, ip_rtx, insn));
@@ -13716,9 +13695,8 @@ thumb_load_double_from_address (rtx *operands)
   switch (GET_CODE (addr))
     {
     case REG:
-      operands[2] = gen_rtx_MEM (SImode,
-				 plus_constant (XEXP (operands[1], 0), 4));
-
+      operands[2] = adjust_address (operands[1], SImode, 4);
+      
       if (REGNO (operands[0]) == REGNO (addr))
 	{
 	  output_asm_insn ("ldr\t%H0, %2", operands);
@@ -13733,9 +13711,8 @@ thumb_load_double_from_address (rtx *operands)
 
     case CONST:
       /* Compute <address> + 4 for the high order load.  */
-      operands[2] = gen_rtx_MEM (SImode,
-				 plus_constant (XEXP (operands[1], 0), 4));
-
+      operands[2] = adjust_address (operands[1], SImode, 4);
+      
       output_asm_insn ("ldr\t%0, %1", operands);
       output_asm_insn ("ldr\t%H0, %2", operands);
       break;
@@ -13776,8 +13753,8 @@ thumb_load_double_from_address (rtx *operands)
       else
 	{
 	  /* Compute <address> + 4 for the high order load.  */
-	  operands[2] = gen_rtx_MEM (SImode,
-				     plus_constant (XEXP (operands[1], 0), 4));
+	  operands[2] = adjust_address (operands[1], SImode, 4);
+	  
 
 	  /* If the computed address is held in the low order register
 	     then load the high order register first, otherwise always
@@ -13798,8 +13775,7 @@ thumb_load_double_from_address (rtx *operands)
     case LABEL_REF:
       /* With no registers to worry about we can just load the value
          directly.  */
-      operands[2] = gen_rtx_MEM (SImode,
-				 plus_constant (XEXP (operands[1], 0), 4));
+      operands[2] = adjust_address (operands[1], SImode, 4);
 
       output_asm_insn ("ldr\t%H0, %2", operands);
       output_asm_insn ("ldr\t%0, %1", operands);
@@ -14694,7 +14670,7 @@ arm_set_return_address (rtx source, rtx scratch)
 
 	  addr = plus_constant (addr, delta);
 	}
-      emit_move_insn (gen_rtx_MEM (Pmode, addr), source);
+      emit_move_insn (gen_frame_mem (Pmode, addr), source);
     }
 }
 
@@ -14744,7 +14720,7 @@ thumb_set_return_address (rtx source, rtx scratch)
       else
 	addr = plus_constant (addr, delta);
 
-      emit_move_insn (gen_rtx_MEM (Pmode, addr), source);
+      emit_move_insn (gen_frame_mem (Pmode, addr), source);
     }
   else
     emit_move_insn (gen_rtx_REG (Pmode, LR_REGNUM), source);
diff --git a/gcc/config/arm/arm.md b/gcc/config/arm/arm.md
index 3bc62de65e9825dedd5ad99fa4f17f8544142c30..5d72af924ef8566b7c3698cc62742acd0bde6b2a 100644
--- a/gcc/config/arm/arm.md
+++ b/gcc/config/arm/arm.md
@@ -3390,36 +3390,6 @@
    (set_attr "predicable" "yes")]
 )
 
-(define_split
-  [(set (match_operand:SI 0 "s_register_operand" "")
-	(zero_extend:SI (match_operand:HI 1 "alignable_memory_operand" "")))
-   (clobber (match_operand:SI 2 "s_register_operand" ""))]
-  "TARGET_ARM && (!arm_arch4)"
-  [(set (match_dup 2) (match_dup 1))
-   (set (match_dup 0) (lshiftrt:SI (match_dup 2) (const_int 16)))]
-  "
-  if ((operands[1] = arm_gen_rotated_half_load (operands[1])) == NULL)
-    FAIL;
-  "
-)
-
-(define_split
-  [(set (match_operand:SI 0 "s_register_operand" "")
-	(match_operator:SI 3 "shiftable_operator"
-	 [(zero_extend:SI (match_operand:HI 1 "alignable_memory_operand" ""))
-	  (match_operand:SI 4 "s_register_operand" "")]))
-   (clobber (match_operand:SI 2 "s_register_operand" ""))]
-  "TARGET_ARM && (!arm_arch4)"
-  [(set (match_dup 2) (match_dup 1))
-   (set (match_dup 0)
-	(match_op_dup 3
-	 [(lshiftrt:SI (match_dup 2) (const_int 16)) (match_dup 4)]))]
-  "
-  if ((operands[1] = arm_gen_rotated_half_load (operands[1])) == NULL)
-    FAIL;
-  "
-)
-
 (define_expand "zero_extendqisi2"
   [(set (match_operand:SI 0 "s_register_operand" "")
 	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "")))]
@@ -3721,10 +3691,8 @@
     rtx mem1, mem2;
     rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
 
-    mem1 = gen_rtx_MEM (QImode, addr);
-    MEM_COPY_ATTRIBUTES (mem1, operands[1]);
-    mem2 = gen_rtx_MEM (QImode, plus_constant (addr, 1));
-    MEM_COPY_ATTRIBUTES (mem2, operands[1]);
+    mem1 = change_address (operands[1], QImode, addr);
+    mem2 = change_address (operands[1], QImode, plus_constant (addr, 1));
     operands[0] = gen_lowpart (SImode, operands[0]);
     operands[1] = mem1;
     operands[2] = gen_reg_rtx (SImode);
@@ -3777,35 +3745,6 @@
   "sxtah%?\\t%0, %2, %1"
 )
 
-(define_split
-  [(set (match_operand:SI                 0 "s_register_operand" "")
-	(sign_extend:SI (match_operand:HI 1 "alignable_memory_operand" "")))
-   (clobber (match_operand:SI             2 "s_register_operand" ""))]
-  "TARGET_ARM && (!arm_arch4)"
-  [(set (match_dup 2) (match_dup 1))
-   (set (match_dup 0) (ashiftrt:SI (match_dup 2) (const_int 16)))]
-  "
-  if ((operands[1] = arm_gen_rotated_half_load (operands[1])) == NULL)
-    FAIL;
-  "
-)
-
-(define_split
-  [(set (match_operand:SI                   0 "s_register_operand" "")
-	(match_operator:SI                  3 "shiftable_operator"
-	 [(sign_extend:SI (match_operand:HI 1 "alignable_memory_operand" ""))
-	  (match_operand:SI                 4 "s_register_operand" "")]))
-   (clobber (match_operand:SI               2 "s_register_operand" ""))]
-  "TARGET_ARM && (!arm_arch4)"
-  [(set (match_dup 2) (match_dup 1))
-   (set (match_dup 0)
-	(match_op_dup 3
-	 [(ashiftrt:SI (match_dup 2) (const_int 16)) (match_dup 4)]))]
-  "if ((operands[1] = arm_gen_rotated_half_load (operands[1])) == NULL)
-     FAIL;
-  "
-)
-
 (define_expand "extendqihi2"
   [(set (match_dup 2)
 	(ashift:SI (match_operand:QI 1 "general_operand" "")
@@ -4750,12 +4689,11 @@
 			   && GET_CODE (base = XEXP (base, 0)) == REG))
 		      && REGNO_POINTER_ALIGN (REGNO (base)) >= 32)
 		    {
-		      HOST_WIDE_INT new_offset = INTVAL (offset) & ~3;
 		      rtx new;
 
-		      new = gen_rtx_MEM (SImode,
-					 plus_constant (base, new_offset));
-	              MEM_COPY_ATTRIBUTES (new, operands[1]);
+		      new = widen_memory_access (operands[1], SImode,
+						 ((INTVAL (offset) & ~3)
+						  - INTVAL (offset)));
 		      emit_insn (gen_movsi (reg, new));
 		      if (((INTVAL (offset) & 2) != 0)
 			  ^ (BYTES_BIG_ENDIAN ? 1 : 0))
@@ -4882,10 +4820,8 @@
     rtx mem1, mem2;
     rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
 
-    mem1 = gen_rtx_MEM (QImode, addr);
-    MEM_COPY_ATTRIBUTES (mem1, operands[1]);
-    mem2 = gen_rtx_MEM (QImode, plus_constant (addr, 1));
-    MEM_COPY_ATTRIBUTES (mem2, operands[1]);
+    mem1 = change_address (operands[1], QImode, addr);
+    mem2 = change_address (operands[1], QImode, plus_constant (addr, 1));
     operands[0] = gen_lowpart (SImode, operands[0]);
     operands[1] = mem1;
     operands[2] = gen_reg_rtx (SImode);
@@ -5233,7 +5169,8 @@
       emit_insn (gen_addsi3 (operands[2], XEXP (XEXP (operands[0], 0), 0),
 			     XEXP (XEXP (operands[0], 0), 1)));
 
-    emit_insn (gen_rtx_SET (VOIDmode, gen_rtx_MEM (DFmode, operands[2]),
+    emit_insn (gen_rtx_SET (VOIDmode,
+			    replace_equiv_address (operands[0], operands[2]),
 			    operands[1]));
 
     if (code == POST_DEC)