diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 5b058244ba110f46e4fa597882956c99c4e1d40e..190a2ed246bf6040a50b08984394ff0300ce9ca9 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,25 @@
+2004-01-27  Kazu Hirata  <kazu@cs.umass.edu>
+
+	* config/iq2000/iq2000-protos.h: Remove the prototype for
+	iq2000_setup_incoming_varargs.
+	* config/iq2000/iq2000.c (TARGET_PROMOTE_FUNCTION_ARGS): New.
+	(TARGET_PROMOTE_FUNCTION_RETURN): Likewise.
+	(TARGET_PROMOTE_PROTOTYPES): Likewise.
+	(TARGET_STRUCT_VALUE_RTX): Likewise.
+	(TARGET_RETURN_IN_MEMORY): Likewise.
+	(TARGET_SETUP_INCOMING_VARARGS): Likewise.
+	(TARGET_STRICT_ARGUMENT_NAMING): Likewise.
+	(iq2000_return_in_memory): Likewise.
+	(iq2000_setup_incoming_varargs): Make it static.  Receive the
+	first argument by reference.
+	* config/iq2000/iq2000.h (PROMOTE_FUNCTION_ARGS): Remove.
+	(PROMOTE_FUNCTION_RETURN): Likewise.
+	(PROMOTE_PROTOTYPES): Likewise.
+	(RETURN_IN_MEMORY): Likewise.
+	(STRUCT_VALUE): Likewise.
+	(SETUP_INCOMING_VARARGS): Likewise.
+	(STRICT_ARGUMENT_NAMING): Likewise.
+
 2004-01-24  James A. Morrison  <ja2morri@uwaterloo.ca>
 
         * fixinc/fixinc.c (test_test): Initialize res.
diff --git a/gcc/config/iq2000/iq2000-protos.h b/gcc/config/iq2000/iq2000-protos.h
index 989bb657ccb65facdf99a55a0891f28da3ea4647..dadcc232dde08ebf33de866fe48c38469ab5f121 100644
--- a/gcc/config/iq2000/iq2000-protos.h
+++ b/gcc/config/iq2000/iq2000-protos.h
@@ -1,5 +1,5 @@
 /* Definitions of target machine for GNU compiler for iq2000.
-   Copyright (C) 2003 Free Software Foundation, Inc.
+   Copyright (C) 2003, 2004 Free Software Foundation, Inc.
 
    This file is part of GCC.
 
@@ -38,7 +38,6 @@ extern int              iq2000_can_use_return_insn (void);
 extern int              function_arg_pass_by_reference (CUMULATIVE_ARGS *, enum machine_mode, tree, int);
 extern int              iq2000_adjust_insn_length (rtx, int);
 extern char *           iq2000_output_conditional_branch (rtx, rtx *, int, int, int, int);
-extern void             iq2000_setup_incoming_varargs (CUMULATIVE_ARGS, int, tree, int*, int);
 extern void             print_operand_address (FILE *, rtx);
 extern void             print_operand (FILE *, rtx, int);
 
diff --git a/gcc/config/iq2000/iq2000.c b/gcc/config/iq2000/iq2000.c
index 5015b86db24f6aeb76779497fdd2828166831e64..59fcc6c1fcbdab44e4b9fb7d4b1297799c97f702 100644
--- a/gcc/config/iq2000/iq2000.c
+++ b/gcc/config/iq2000/iq2000.c
@@ -1,5 +1,5 @@
 /* Subroutines used for code generation on Vitesse IQ2000 processors
-   Copyright (C) 2003 Free Software Foundation, Inc.
+   Copyright (C) 2003, 2004 Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -163,9 +163,14 @@ static struct machine_function* iq2000_init_machine_status (void);
 static void iq2000_select_rtx_section (enum machine_mode, rtx, unsigned HOST_WIDE_INT);
 static void iq2000_init_builtins      (void);
 static rtx  iq2000_expand_builtin     (tree, rtx, rtx, enum machine_mode, int);
+static bool iq2000_return_in_memory   (tree, tree);
+static void iq2000_setup_incoming_varargs (CUMULATIVE_ARGS *,
+					   enum machine_mode, tree, int *,
+					   int);
 static bool iq2000_rtx_costs          (rtx, int, int, int *);
 static int  iq2000_address_cost       (rtx);
 static void iq2000_select_section     (tree, int, unsigned HOST_WIDE_INT);
+static bool iq2000_return_in_memory   (tree, tree);
 
 #undef  TARGET_INIT_BUILTINS
 #define TARGET_INIT_BUILTINS 		iq2000_init_builtins
@@ -180,6 +185,23 @@ static void iq2000_select_section     (tree, int, unsigned HOST_WIDE_INT);
 #undef  TARGET_ASM_SELECT_SECTION
 #define TARGET_ASM_SELECT_SECTION	iq2000_select_section
 
+#undef  TARGET_PROMOTE_FUNCTION_ARGS
+#define TARGET_PROMOTE_FUNCTION_ARGS	hook_bool_tree_true
+#undef  TARGET_PROMOTE_FUNCTION_RETURN
+#define TARGET_PROMOTE_FUNCTION_RETURN	hook_bool_tree_true
+#undef  TARGET_PROMOTE_PROTOTYPES
+#define TARGET_PROMOTE_PROTOTYPES	hook_bool_tree_true
+
+#undef  TARGET_STRUCT_VALUE_RTX
+#define TARGET_STRUCT_VALUE_RTX		hook_rtx_tree_int_null
+#undef  TARGET_RETURN_IN_MEMORY
+#define TARGET_RETURN_IN_MEMORY		iq2000_return_in_memory
+
+#undef  TARGET_SETUP_INCOMING_VARARGS
+#define TARGET_SETUP_INCOMING_VARARGS	iq2000_setup_incoming_varargs
+#undef  TARGET_STRICT_ARGUMENT_NAMING
+#define TARGET_STRICT_ARGUMENT_NAMING	hook_bool_CUMULATIVE_ARGS_true
+
 struct gcc_target targetm = TARGET_INITIALIZER;
 
 /* Return 1 if OP can be used as an operand where a register or 16 bit unsigned
@@ -2642,8 +2664,8 @@ iq2000_function_value (tree valtype, tree func ATTRIBUTE_UNUSED)
   enum machine_mode mode = TYPE_MODE (valtype);
   int unsignedp = TREE_UNSIGNED (valtype);
 
-  /* Since we define PROMOTE_FUNCTION_RETURN, we must promote the mode
-     just as PROMOTE_MODE does.  */
+  /* Since we define TARGET_PROMOTE_FUNCTION_RETURN that returns true,
+     we must promote the mode just as PROMOTE_MODE does.  */
   mode = promote_mode (valtype, mode, &unsignedp, 1);
 
   return gen_rtx_REG (mode, reg);
@@ -3262,20 +3284,28 @@ iq2000_expand_builtin (tree exp, rtx target, rtx subtarget ATTRIBUTE_UNUSED,
   return NULL_RTX;
 }
 
-void
-iq2000_setup_incoming_varargs (CUMULATIVE_ARGS cum, int mode ATTRIBUTE_UNUSED,
+static bool
+iq2000_return_in_memory (tree type, tree fntype ATTRIBUTE_UNUSED)
+{
+  return ((int_size_in_bytes (type) > (2 * UNITS_PER_WORD))
+	  || (int_size_in_bytes (type) == -1));
+}
+
+static void
+iq2000_setup_incoming_varargs (CUMULATIVE_ARGS *cum,
+			       enum machine_mode mode ATTRIBUTE_UNUSED,
 			       tree type ATTRIBUTE_UNUSED, int * pretend_size,
 			       int no_rtl)
 {
-  unsigned int iq2000_off = (! (cum).last_arg_fp); 
-  unsigned int iq2000_fp_off = ((cum).last_arg_fp); 
+  unsigned int iq2000_off = ! cum->last_arg_fp; 
+  unsigned int iq2000_fp_off = cum->last_arg_fp; 
 
-  if (((cum).arg_words < MAX_ARGS_IN_REGISTERS - iq2000_off))
+  if ((cum->arg_words < MAX_ARGS_IN_REGISTERS - iq2000_off))
     {
       int iq2000_save_gp_regs 
-	= MAX_ARGS_IN_REGISTERS - (cum).arg_words - iq2000_off; 
+	= MAX_ARGS_IN_REGISTERS - cum->arg_words - iq2000_off; 
       int iq2000_save_fp_regs 
-        = (MAX_ARGS_IN_REGISTERS - (cum).fp_arg_words - iq2000_fp_off); 
+        = (MAX_ARGS_IN_REGISTERS - cum->fp_arg_words - iq2000_fp_off); 
 
       if (iq2000_save_gp_regs < 0) 
 	iq2000_save_gp_regs = 0; 
@@ -3287,7 +3317,7 @@ iq2000_setup_incoming_varargs (CUMULATIVE_ARGS cum, int mode ATTRIBUTE_UNUSED,
 
       if (! (no_rtl)) 
 	{
-	  if ((cum).arg_words < MAX_ARGS_IN_REGISTERS - iq2000_off) 
+	  if (cum->arg_words < MAX_ARGS_IN_REGISTERS - iq2000_off) 
 	    {
 	      rtx ptr, mem; 
 	      ptr = plus_constant (virtual_incoming_args_rtx, 
@@ -3295,7 +3325,7 @@ iq2000_setup_incoming_varargs (CUMULATIVE_ARGS cum, int mode ATTRIBUTE_UNUSED,
 				      * UNITS_PER_WORD)); 
 	      mem = gen_rtx_MEM (BLKmode, ptr); 
 	      move_block_from_reg 
-		((cum).arg_words + GP_ARG_FIRST + iq2000_off, 
+		(cum->arg_words + GP_ARG_FIRST + iq2000_off, 
 		 mem, 
 		 iq2000_save_gp_regs);
 	    } 
diff --git a/gcc/config/iq2000/iq2000.h b/gcc/config/iq2000/iq2000.h
index a54856a402be97823ef15995ad5e87859c3ebdde..3d04c0e59b8e587b2feaf4ccfd52480e1e838d14 100644
--- a/gcc/config/iq2000/iq2000.h
+++ b/gcc/config/iq2000/iq2000.h
@@ -1,6 +1,6 @@
 /* Definitions of target machine for GNU compiler.  
    Vitesse IQ2000 processors
-   Copyright (C) 2003 Free Software Foundation, Inc.
+   Copyright (C) 2003, 2004 Free Software Foundation, Inc.
 
    This file is part of GCC.
 
@@ -155,10 +155,6 @@ extern int	target_flags;
       && GET_MODE_SIZE (MODE) < 4)		\
     (MODE) = SImode;
 
-#define PROMOTE_FUNCTION_ARGS
-
-#define PROMOTE_FUNCTION_RETURN
-
 #define PARM_BOUNDARY 32
 
 #define STACK_BOUNDARY 64
@@ -427,8 +423,6 @@ enum reg_class
 
 /* Passing Function Arguments on the Stack.  */
 
-#define PROMOTE_PROTOTYPES 1
-
 /* #define PUSH_ROUNDING(BYTES) 0 */
 
 #define ACCUMULATE_OUTGOING_ARGS 1
@@ -520,15 +514,7 @@ typedef struct iq2000_args
 
 /* How Large Values are Returned.  */
 
-#define RETURN_IN_MEMORY(TYPE)						 \
-  (((int_size_in_bytes (TYPE)						 \
-       > (2 * UNITS_PER_WORD)) 						 \
-      || (int_size_in_bytes (TYPE) == -1)))
-
 #define DEFAULT_PCC_STRUCT_RETURN 0
-
-#define STRUCT_VALUE 0
-
 
 /* Function Entry and Exit.  */
 
@@ -557,11 +543,6 @@ typedef struct iq2000_args
 
 /* Implementing the Varargs Macros.  */
 
-#define SETUP_INCOMING_VARARGS(CUM,MODE,TYPE,PRETEND_SIZE,NO_RTL)	\
-  iq2000_setup_incoming_varargs (CUM,MODE,TYPE,&PRETEND_SIZE,NO_RTL);
-
-#define STRICT_ARGUMENT_NAMING  1
-
 #define EXPAND_BUILTIN_VA_START(valist, nextarg) \
   iq2000_va_start (valist, nextarg)