From 5e6a42d9e45fd193b3cc6d1a41f6604b8147e6af Mon Sep 17 00:00:00 2001
From: Michael Hayes <m.hayes@elec.canterbury.ac.nz>
Date: Sat, 9 Jan 1999 18:46:10 +0000
Subject: [PATCH] c4x.c: Include system.h.

	* config/c4x/c4x.c: Include system.h.
 	(c4x_caller_save_map): Disable caller save for RC.
	(c4x_optimization_options): Disable scheduling before reload.
	(valid_parallel_load_store) : Define return type as int.
	Remove unused variable regs.
	* config/c4x/c4x.h (REGISTER_MOVE_COST): Make independent of register
	class.
	* config/c4x/c4x.md (rotlqi3, rotrqi3): Fix up emitted RTL to
	handle rotations.
	(*db, decrement_and_branch_until_zero): Fix up constraints
	to keep reload happy.

From-SVN: r24600
---
 gcc/ChangeLog         | 14 ++++++++++++
 gcc/config/c4x/c4x.c  | 21 +++++++++--------
 gcc/config/c4x/c4x.h  |  9 ++++----
 gcc/config/c4x/c4x.md | 52 ++++++++++++++++++++++++++++++++-----------
 4 files changed, 67 insertions(+), 29 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index ab5938e7d21a..6e510aa6f70a 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,17 @@
+Sun Jan 10 15:35:41 1999  Michael Hayes  <m.hayes@elec.canterbury.ac.nz>
+
+	* config/c4x/c4x.c: Include system.h.
+ 	(c4x_caller_save_map): Disable caller save for RC.
+	(c4x_optimization_options): Disable scheduling before reload.
+	(valid_parallel_load_store) : Define return type as int.  
+	Remove unused variable regs.
+	* config/c4x/c4x.h (REGISTER_MOVE_COST): Make independent of register
+	class.
+	* config/c4x/c4x.md (rotlqi3, rotrqi3): Fix up emitted RTL to
+	handle rotations.
+	(*db, decrement_and_branch_until_zero): Fix up constraints
+	to keep reload happy.
+
 Sat Jan  9 18:35:29 1999  Richard Henderson  <rth@cygnus.com>
 
 	* tree.c (make_node): Call bzero instead of inline clear.
diff --git a/gcc/config/c4x/c4x.c b/gcc/config/c4x/c4x.c
index a4aa23a21a96..f8a643185009 100644
--- a/gcc/config/c4x/c4x.c
+++ b/gcc/config/c4x/c4x.c
@@ -1,5 +1,5 @@
 /* Subroutines for assembler code output on the TMS320C[34]x
-   Copyright (C) 1994, 1995, 1996, 1997 Free Software Foundation, Inc.
+   Copyright (C) 1994-98, 1999 Free Software Foundation, Inc.
 
    Contributed by Michael Hayes (m.hayes@elec.canterbury.ac.nz)
               and Herman Ten Brugge (Haj.Ten.Brugge@net.HCC.nl).
@@ -22,10 +22,8 @@
    Boston, MA 02111-1307, USA.  */
 
 /* Some output-actions in c4x.md need these.  */
-#include <stdio.h>
-#include <stdlib.h>
-#include <stdarg.h>
 #include "config.h"
+#include "system.h"
 #include "toplev.h"
 #include "rtl.h"
 #include "regs.h"
@@ -121,7 +119,7 @@ enum machine_mode c4x_caller_save_map[FIRST_PSEUDO_REGISTER] =
   VOIDmode,			/* IIF/IOF                      No  */
   QImode,			/* RS           QI              No  */
   QImode,			/* RE           QI              No  */
-  QImode,			/* RC           QI              No  */
+  VOIDmode,			/* RC           QI              No  */
   QFmode,			/* R8           QI, QF, HF      QI  */
   HFmode,			/* R9           QI, QF, HF      No  */
   HFmode,			/* R10          QI, QF, HF      No  */
@@ -202,11 +200,6 @@ c4x_override_options ()
   /* Convert foo / 8.0 into foo * 0.125, etc.  */
   flag_fast_math = 1;
 
-  /* We should phase out the following at some stage.
-     This provides compatibility with the old -mno-rptb option.  */
-  if (! TARGET_RPTB && flag_branch_on_count_reg)
-    flag_branch_on_count_reg = 0;
-
   /* We should phase out the following at some stage.
      This provides compatibility with the old -mno-aliases option.  */
   if (! TARGET_ALIASES && ! flag_argument_noalias)
@@ -219,6 +212,12 @@ c4x_optimization_options (level, size)
      int level;
      int size ATTRIBUTE_UNUSED;
 {
+  /* Scheduling before register allocation can screw up global
+     register allocation, especially for functions that use MPY||ADD
+     instructions.  The benefit we gain we get by scheduling before
+     register allocation is probably marginal anyhow.  */
+  flag_schedule_insns = 0;
+
   /* When optimizing, enable use of RPTB instruction.  */
   if (level >= 1)
     flag_branch_on_count_reg = 1;
@@ -3194,6 +3193,7 @@ c4x_label_conflict (insn, jump, db)
 
 /* Validate combination of operands for parallel load/store instructions.  */
 
+int
 valid_parallel_load_store (operands, mode)
      rtx *operands;
      enum machine_mode mode ATTRIBUTE_UNUSED;
@@ -3254,7 +3254,6 @@ valid_parallel_operands_4 (operands, mode)
      rtx *operands;
      enum machine_mode mode ATTRIBUTE_UNUSED;
 {
-  int regs = 0;
   rtx op0 = operands[0];
   rtx op2 = operands[2];
 
diff --git a/gcc/config/c4x/c4x.h b/gcc/config/c4x/c4x.h
index a2053d301c98..2a0a7c045d48 100644
--- a/gcc/config/c4x/c4x.h
+++ b/gcc/config/c4x/c4x.h
@@ -1,5 +1,5 @@
 /* Definitions of target machine for GNU compiler.  TMS320C[34]x
-   Copyright (C) 1994, 1995, 1996, 1997 Free Software Foundation, Inc.
+   Copyright (C) 1994-98, 1999 Free Software Foundation, Inc.
 
    Contributed by Michael Hayes (m.hayes@elec.canterbury.ac.nz)
               and Herman Ten Brugge (Haj.Ten.Brugge@net.HCC.nl).
@@ -1713,11 +1713,10 @@ if (REG_P (OP1) && ! REG_P (OP0))			\
 #define EXPENSIVE_CLASS_P(CLASS) (ADDR_CLASS_P(CLASS) \
                           || INDEX_CLASS_P(CLASS) || (CLASS) == SP_REG)
 
-/* Make the Rx register a little easier to use so they are used for
-   calculations and the ARx registers are used for addressing. */
+/* Compute extra cost of moving data between one register class
+   and another.  */
 
-#define REGISTER_MOVE_COST(FROM, TO) \
-(EXPENSIVE_CLASS_P(TO) ? 5 : EXPENSIVE_CLASS_P(FROM) ? 4 : 3)
+#define REGISTER_MOVE_COST(FROM, TO)	2
 
 /* Memory move cost is same as fast register move.  Maybe this should
    be bumped up? */
diff --git a/gcc/config/c4x/c4x.md b/gcc/config/c4x/c4x.md
index 1a0eec77f517..1e3d343eba4b 100644
--- a/gcc/config/c4x/c4x.md
+++ b/gcc/config/c4x/c4x.md
@@ -1,7 +1,7 @@
 ;; Machine description for the TMS320C[34]x for GNU C compiler
-;; Copyright (C) 1994, 95-98, 1999 Free Software Foundation, Inc.
+;; Copyright (C) 1994-98, 1999 Free Software Foundation, Inc.
 
-;; Contributed by Michael Hayes (m.hayes@elec.canterbury.cri.nz)
+;; Contributed by Michael Hayes (m.hayes@elec.canterbury.ac.nz)
 ;;            and Herman Ten Brugge (Haj.Ten.Brugge@net.HCC.nl)
 
 ;; This file is part of GNU CC.
@@ -369,7 +369,7 @@
 
 (define_attr "in_annul_slot_3" "false,true"
   (if_then_else (and (eq_attr "cpu" "c4x")
-		     (eq_attr "type" "!jump,call,rets,jmpc,db,dbc,repeat,repeat_top,laj,push,pop,multi"))
+		     (eq_attr "type" "!jump,call,rets,jmpc,unarycc,binarycc,db,dbc,repeat,repeat_top,laj,push,pop,multi"))
 		(const_string "true")
 		(const_string "false")))
 
@@ -1458,19 +1458,26 @@
                               (match_operand:QI 2 "const_int_operand" "")))
               (clobber (reg:CC 21))])]
   ""
-  "if (INTVAL (operands[2]) >= 4)
+  "if (INTVAL (operands[2]) > 4)
      FAIL; /* Open code as two shifts and an or */
    if (INTVAL (operands[2]) > 1)
      {
         int i;
+	rtx tmp;
 
         /* If we have 4 or fewer shifts, then it is probably faster
            to emit separate ROL instructions.  A C3x requires
            at least 4 instructions (a C4x requires at least 3), to
            perform a rotation by shifts.  */
 
-        for (i = 0; i < INTVAL (operands[2]); i++)
-          emit_insn (gen_rotl_1_clobber (operands[0], operands[1]));
+	tmp = operands[1];
+        for (i = 0; i < INTVAL (operands[2]) - 1; i++)
+	  {
+   	    tmp = gen_reg_rtx (QImode);
+            emit_insn (gen_rotl_1_clobber (tmp, operands[1]));
+	    operands[1] = tmp;
+	  }
+        emit_insn (gen_rotl_1_clobber (operands[0], tmp));
         DONE;
      }")
 
@@ -1493,19 +1500,26 @@
                                 (match_operand:QI 2 "const_int_operand" "")))
               (clobber (reg:CC 21))])]
   ""
-  "if (INTVAL (operands[2]) >= 4)
+  "if (INTVAL (operands[2]) > 4)
      FAIL; /* Open code as two shifts and an or */
    if (INTVAL (operands[2]) > 1)
      {
         int i;
+	rtx tmp;
  
         /* If we have 4 or fewer shifts, then it is probably faster
            to emit separate ROL instructions.  A C3x requires
            at least 4 instructions (a C4x requires at least 3), to
            perform a rotation by shifts.  */
  
-        for (i = 0; i < INTVAL (operands[2]); i++)
-          emit_insn (gen_rotr_1_clobber (operands[0], operands[1]));
+	tmp = operands[1];
+        for (i = 0; i < INTVAL (operands[2]) - 1; i++)
+	  {
+   	    tmp = gen_reg_rtx (QImode);
+            emit_insn (gen_rotr_1_clobber (tmp, operands[1]));
+	    operands[1] = tmp;
+	  }
+        emit_insn (gen_rotr_1_clobber (operands[0], tmp));
         DONE;
      }")
 
@@ -4484,11 +4498,11 @@
 ; have an option to disable this instruction.
 (define_insn "*db"
   [(set (pc)
-        (if_then_else (ne (match_operand:QI 2 "addr_reg_operand" "0,0,0,0")
+        (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
                           (const_int 0))
                       (label_ref (match_operand 1 "" ""))
                       (pc)))
-   (set (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
+   (set (match_dup 0)
         (plus:QI (match_dup 0)
                  (const_int -1)))
    (clobber (reg:CC_NOOV 21))]
@@ -4505,14 +4519,26 @@
   "
   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
 
+
+; This insn is used for some loop tests, typically loops reversed when
+; strength reduction is used.  It is actually created when the instruction
+; combination phase combines the special loop test.  Since this insn
+; is both a jump insn and has an output, it must deal with its own
+; reloads, hence the `m' constraints. 
+
+; The C4x does the decrement and then compares the result against zero.
+; It branches if the result was greater than or equal to zero.
+; In the RTL the comparison and decrement are assumed to happen
+; at the same time so we bias the iteration counter with by -1
+; when we make the test.
 (define_insn "decrement_and_branch_until_zero"
   [(set (pc)
-        (if_then_else (ge (plus:QI (match_operand:QI 2 "addr_reg_operand" "0,0,0,0")
+        (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
 			           (const_int -1))
 			  (const_int 0))
                       (label_ref (match_operand 1 "" ""))
                       (pc)))
-   (set (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
+   (set (match_dup 0)
         (plus:QI (match_dup 0)
                  (const_int -1)))
    (clobber (reg:CC_NOOV 21))]
-- 
GitLab