From ac32b25eb886014b94e40d2e74f30a826321281c Mon Sep 17 00:00:00 2001
From: Ulrich Weigand <uweigand@de.ibm.com>
Date: Sat, 18 Oct 2003 22:24:37 +0000
Subject: [PATCH] s390-protos.h (shift_count_operand): Add prototype.

	* config/s390/s390-protos.h (shift_count_operand): Add prototype.
	* config/s390/s390.c (shift_count_operand): New function.
	(s390_extra_constraint): Use it to implement 'Y' constraint.
	(print_shift_count_operand): New function.
	(print_operand): Use it to implement '%Y'.
	* config/s390/s390.h (EXTRA_ADDRESS_CONSTRAINT): Add 'Y' constraint.
	(PREDICATE_CODES): Add shift_count_operand.
	* config/s390/s390.md ("rotldi3"): Merge alternatives,
	using "shift_count_operand" predicate and "Y" constraint,
	and "%Y" to output the combined shift count.
	("rotlsi3"): Likewise.
	("ashldi3", "*ashldi3_31", "*ashldi3_64"): Likewise.
	("ashrdi3", "*ashrdi3_31", "*ashrdi3_64", "*ashrdi3_cc_31",
	"*ashrdi3_cc_64", "*ashrdi3_cconly_31", "*ashrdi3_cconly_64"): Likewise.
	("ashlsi3", "ashrsi3", "*ashrsi3_cc", "*ashrsi3_cconly"): Likewise.
	("lshrdi3", "*lshrdi3_31", "*lshrdi3_64"): Likewise.
	("lshrsi3"): Likewise.

From-SVN: r72661
---
 gcc/ChangeLog                 |  20 ++++
 gcc/config/s390/s390-protos.h |   1 +
 gcc/config/s390/s390.c        |  82 ++++++++++++++++
 gcc/config/s390/s390.h        |   3 +-
 gcc/config/s390/s390.md       | 180 ++++++++++++++--------------------
 5 files changed, 178 insertions(+), 108 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 32e1d67d828b..7810f95d336a 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,23 @@
+2003-10-18  Ulrich Weigand  <uweigand@de.ibm.com>
+
+	* config/s390/s390-protos.h (shift_count_operand): Add prototype.
+	* config/s390/s390.c (shift_count_operand): New function.
+	(s390_extra_constraint): Use it to implement 'Y' constraint.
+	(print_shift_count_operand): New function.
+	(print_operand): Use it to implement '%Y'.
+	* config/s390/s390.h (EXTRA_ADDRESS_CONSTRAINT): Add 'Y' constraint.
+	(PREDICATE_CODES): Add shift_count_operand.
+	* config/s390/s390.md ("rotldi3"): Merge alternatives, 
+	using "shift_count_operand" predicate and "Y" constraint,
+	and "%Y" to output the combined shift count.
+	("rotlsi3"): Likewise.
+	("ashldi3", "*ashldi3_31", "*ashldi3_64"): Likewise.
+	("ashrdi3", "*ashrdi3_31", "*ashrdi3_64", "*ashrdi3_cc_31", 
+	"*ashrdi3_cc_64", "*ashrdi3_cconly_31", "*ashrdi3_cconly_64"): Likewise.
+	("ashlsi3", "ashrsi3", "*ashrsi3_cc", "*ashrsi3_cconly"): Likewise.
+	("lshrdi3", "*lshrdi3_31", "*lshrdi3_64"): Likewise.
+	("lshrsi3"): Likewise.
+
 2003-10-18  Gunther Nikl  <gni@gecko.de>
 
 	* config/m68k/m68k.c (m68k_output_function_epilogue): Add missing
diff --git a/gcc/config/s390/s390-protos.h b/gcc/config/s390/s390-protos.h
index 76ceccdc5127..e99de323336b 100644
--- a/gcc/config/s390/s390-protos.h
+++ b/gcc/config/s390/s390-protos.h
@@ -36,6 +36,7 @@ extern int consttable_operand (rtx, enum machine_mode);
 extern int larl_operand (rtx, enum machine_mode);
 extern int s_operand (rtx, enum machine_mode);
 extern int s_imm_operand (rtx, enum machine_mode);
+extern int shift_count_operand (rtx, enum machine_mode);
 extern int bras_sym_operand (rtx, enum machine_mode);
 extern int load_multiple_operation (rtx, enum machine_mode);
 extern int store_multiple_operation (rtx, enum machine_mode);
diff --git a/gcc/config/s390/s390.c b/gcc/config/s390/s390.c
index 6d56b0278b15..10a69676f8b1 100644
--- a/gcc/config/s390/s390.c
+++ b/gcc/config/s390/s390.c
@@ -211,6 +211,7 @@ static int s390_short_displacement (rtx);
 static int s390_decompose_address (rtx, struct s390_address *);
 static rtx get_thread_pointer (void);
 static rtx legitimize_tls_address (rtx, rtx);
+static void print_shift_count_operand (FILE *, rtx);
 static const char *get_some_local_dynamic_name (void);
 static int get_some_local_dynamic_name_1 (rtx *, void *);
 static int reg_used_in_mem_p (int, rtx);
@@ -1274,6 +1275,45 @@ s_imm_operand (register rtx op, enum machine_mode mode)
   return general_s_operand (op, mode, 1);
 }
 
+/* Return true if OP a valid shift count operand.
+   OP is the current operation.
+   MODE is the current operation mode.  */
+
+int
+shift_count_operand (rtx op, enum machine_mode mode)
+{
+  HOST_WIDE_INT offset = 0;
+
+  if (! check_mode (op, &mode))
+    return 0;
+
+  /* We can have an integer constant, an address register,
+     or a sum of the two.  Note that reload already checks
+     that any register present is an address register, so
+     we just check for any register here.  */
+  if (GET_CODE (op) == CONST_INT)
+    {
+      offset = INTVAL (op);
+      op = NULL_RTX;
+    }
+  if (op && GET_CODE (op) == PLUS && GET_CODE (XEXP (op, 1)) == CONST_INT)
+    {
+      offset = INTVAL (XEXP (op, 1));
+      op = XEXP (op, 0);
+    }
+  while (op && GET_CODE (op) == SUBREG)
+    op = SUBREG_REG (op);
+  if (op && GET_CODE (op) != REG)
+    return 0;
+
+  /* Unfortunately we have to reject constants that are invalid
+     for an address, or else reload will get confused.  */
+  if (!DISP_IN_RANGE (offset))
+    return 0;
+
+  return 1;
+}
+
 /* Return true if DISP is a valid short displacement.  */
 
 static int
@@ -1383,6 +1423,9 @@ s390_extra_constraint (rtx op, int c)
 	return 0;
       break;
 
+    case 'Y':
+      return shift_count_operand (op, VOIDmode);
+
     default:
       return 0;
     }
@@ -3281,6 +3324,40 @@ s390_delegitimize_address (rtx orig_x)
   return orig_x;
 }
 
+/* Output shift count operand OP to stdio stream FILE.  */
+
+static void
+print_shift_count_operand (FILE *file, rtx op)
+{
+  HOST_WIDE_INT offset = 0;
+
+  /* We can have an integer constant, an address register,
+     or a sum of the two.  */
+  if (GET_CODE (op) == CONST_INT)
+    {
+      offset = INTVAL (op);
+      op = NULL_RTX;
+    }
+  if (op && GET_CODE (op) == PLUS && GET_CODE (XEXP (op, 1)) == CONST_INT)
+    {
+      offset = INTVAL (XEXP (op, 1));
+      op = XEXP (op, 0);
+    }
+  while (op && GET_CODE (op) == SUBREG)
+    op = SUBREG_REG (op);
+
+  /* Sanity check.  */
+  if (op && (GET_CODE (op) != REG
+	     || REGNO (op) >= FIRST_PSEUDO_REGISTER
+	     || REGNO_REG_CLASS (REGNO (op)) != ADDR_REGS))
+    abort ();
+
+  /* Shift counts are truncated to the low six bits anyway.  */
+  fprintf (file, HOST_WIDE_INT_PRINT_DEC, offset & 63);
+  if (op)
+    fprintf (file, "(%s)", reg_names[REGNO (op)]);
+}
+
 /* Locate some local-dynamic symbol still in use by this function
    so that we can print its name in local-dynamic base patterns.  */
 
@@ -3451,6 +3528,7 @@ print_operand_address (FILE *file, rtx addr)
     'R': print only the base register of a memory reference.
     'N': print the second word of a DImode operand.
     'M': print the second word of a TImode operand.
+    'Y': print shift count operand.
 
     'b': print integer X as if it's an unsigned byte.
     'x': print integer X as if it's an unsigned word.
@@ -3540,6 +3618,10 @@ print_operand (FILE *file, rtx x, int code)
       else
         abort ();
       break;
+
+    case 'Y':
+      print_shift_count_operand (file, x);
+      return;
     }
 
   switch (GET_CODE (x))
diff --git a/gcc/config/s390/s390.h b/gcc/config/s390/s390.h
index 1c3241c63e3b..1463b5035b64 100644
--- a/gcc/config/s390/s390.h
+++ b/gcc/config/s390/s390.h
@@ -544,7 +544,7 @@ extern const enum reg_class regclass_map[FIRST_PSEUDO_REGISTER];
 #define EXTRA_MEMORY_CONSTRAINT(C, STR)				\
   ((C) == 'Q' || (C) == 'R' || (C) == 'S' || (C) == 'T')
 #define EXTRA_ADDRESS_CONSTRAINT(C, STR)			\
-  ((C) == 'U' || (C) == 'W')
+  ((C) == 'U' || (C) == 'W' || (C) == 'Y')
 
 
 /* Stack layout and calling conventions.  */
@@ -1023,6 +1023,7 @@ do {									\
 #define PREDICATE_CODES							\
   {"s_operand",       { SUBREG, MEM }},					\
   {"s_imm_operand",   { CONST_INT, CONST_DOUBLE, SUBREG, MEM }},	\
+  {"shift_count_operand", { REG, SUBREG, PLUS, CONST_INT }},		\
   {"bras_sym_operand",{ SYMBOL_REF, CONST }},				\
   {"larl_operand",    { SYMBOL_REF, CONST, CONST_INT, CONST_DOUBLE }},	\
   {"load_multiple_operation", {PARALLEL}},			        \
diff --git a/gcc/config/s390/s390.md b/gcc/config/s390/s390.md
index 5f49e6ab1d13..9b3d009a7f2e 100644
--- a/gcc/config/s390/s390.md
+++ b/gcc/config/s390/s390.md
@@ -5982,13 +5982,11 @@
 ;
 
 (define_insn "rotldi3"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-	(rotate:DI (match_operand:DI 1 "register_operand" "d,d")
-		   (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:DI 0 "register_operand" "=d")
+	(rotate:DI (match_operand:DI 1 "register_operand" "d")
+		   (match_operand:SI 2 "shift_count_operand" "Y")))]
   "TARGET_64BIT"
-  "@
-   rllg\t%0,%1,%c2
-   rllg\t%0,%1,0(%2)"
+  "rllg\t%0,%1,%Y2"
   [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
@@ -5997,13 +5995,11 @@
 ;
 
 (define_insn "rotlsi3"
-  [(set (match_operand:SI 0 "register_operand" "=d,d")
-	(rotate:SI (match_operand:SI 1 "register_operand" "d,d")
-		   (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:SI 0 "register_operand" "=d")
+	(rotate:SI (match_operand:SI 1 "register_operand" "d")
+		   (match_operand:SI 2 "shift_count_operand" "Y")))]
   "TARGET_CPU_ZARCH"
-  "@
-   rll\t%0,%1,%c2
-   rll\t%0,%1,0(%2)"
+  "rll\t%0,%1,%Y2"
   [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
@@ -6019,29 +6015,25 @@
 (define_expand "ashldi3"
   [(set (match_operand:DI 0 "register_operand" "")
         (ashift:DI (match_operand:DI 1 "register_operand" "")
-                   (match_operand:SI 2 "nonmemory_operand" "")))]
+                   (match_operand:SI 2 "shift_count_operand" "")))]
   ""
   "")
 
 (define_insn "*ashldi3_31"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-        (ashift:DI (match_operand:DI 1 "register_operand" "0,0")
-                   (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:DI 0 "register_operand" "=d")
+        (ashift:DI (match_operand:DI 1 "register_operand" "0")
+                   (match_operand:SI 2 "shift_count_operand" "Y")))]
   "!TARGET_64BIT"
-  "@
-   sldl\t%0,%c2
-   sldl\t%0,0(%2)"
+  "sldl\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
 (define_insn "*ashldi3_64"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-        (ashift:DI (match_operand:DI 1 "register_operand" "d,d")
-                   (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:DI 0 "register_operand" "=d")
+        (ashift:DI (match_operand:DI 1 "register_operand" "d")
+                   (match_operand:SI 2 "shift_count_operand" "Y")))]
   "TARGET_64BIT"
-  "@
-   sllg\t%0,%1,%2
-   sllg\t%0,%1,0(%2)"
+  "sllg\t%0,%1,%Y2"
   [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
@@ -6053,86 +6045,74 @@
   [(parallel
     [(set (match_operand:DI 0 "register_operand" "")
           (ashiftrt:DI (match_operand:DI 1 "register_operand" "")
-                       (match_operand:SI 2 "nonmemory_operand" "")))
+                       (match_operand:SI 2 "shift_count_operand" "")))
      (clobber (reg:CC 33))])]
   ""
   "")
 
 (define_insn "*ashrdi3_cc_31"
   [(set (reg 33)
-        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "0,0")
-                              (match_operand:SI 2 "nonmemory_operand" "J,a"))
+        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "0")
+                              (match_operand:SI 2 "shift_count_operand" "Y"))
                  (const_int 0)))
-   (set (match_operand:DI 0 "register_operand" "=d,d")
+   (set (match_operand:DI 0 "register_operand" "=d")
         (ashiftrt:DI (match_dup 1) (match_dup 2)))]
   "!TARGET_64BIT && s390_match_ccmode(insn, CCSmode)"
-  "@
-   srda\t%0,%c2
-   srda\t%0,0(%2)"
+  "srda\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
 (define_insn "*ashrdi3_cconly_31"
   [(set (reg 33)
-        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "0,0")
-                              (match_operand:SI 2 "nonmemory_operand" "J,a"))
+        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "0")
+                              (match_operand:SI 2 "shift_count_operand" "Y"))
                  (const_int 0)))
-   (clobber (match_scratch:DI 0 "=d,d"))]
+   (clobber (match_scratch:DI 0 "=d"))]
   "!TARGET_64BIT && s390_match_ccmode(insn, CCSmode)"
-  "@
-   srda\t%0,%c2
-   srda\t%0,0(%2)"
+  "srda\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
 (define_insn "*ashrdi3_31"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-        (ashiftrt:DI (match_operand:DI 1 "register_operand" "0,0")
-                     (match_operand:SI 2 "nonmemory_operand" "J,a")))
+  [(set (match_operand:DI 0 "register_operand" "=d")
+        (ashiftrt:DI (match_operand:DI 1 "register_operand" "0")
+                     (match_operand:SI 2 "shift_count_operand" "Y")))
    (clobber (reg:CC 33))]
   "!TARGET_64BIT"
-  "@
-   srda\t%0,%c2
-   srda\t%0,0(%2)"
+  "srda\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
 (define_insn "*ashrdi3_cc_64"
   [(set (reg 33)
-        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "d,d")
-                              (match_operand:SI 2 "nonmemory_operand" "J,a"))
+        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "d")
+                              (match_operand:SI 2 "shift_count_operand" "Y"))
                  (const_int 0)))
-   (set (match_operand:DI 0 "register_operand" "=d,d")
+   (set (match_operand:DI 0 "register_operand" "=d")
         (ashiftrt:DI (match_dup 1) (match_dup 2)))]
   "s390_match_ccmode(insn, CCSmode) && TARGET_64BIT"
-  "@
-   srag\t%0,%1,%c2
-   srag\t%0,%1,0(%2)"
+  "srag\t%0,%1,%Y2"
   [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
 (define_insn "*ashrdi3_cconly_64"
   [(set (reg 33)
-        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "d,d")
-                              (match_operand:SI 2 "nonmemory_operand" "J,a"))
+        (compare (ashiftrt:DI (match_operand:DI 1 "register_operand" "d")
+                              (match_operand:SI 2 "shift_count_operand" "Y"))
                  (const_int 0)))
-   (clobber (match_scratch:DI 0 "=d,d"))]
+   (clobber (match_scratch:DI 0 "=d"))]
   "s390_match_ccmode(insn, CCSmode) && TARGET_64BIT"
-  "@
-   srag\t%0,%1,%c2
-   srag\t%0,%1,0(%2)"
+  "srag\t%0,%1,%Y2"
   [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
 (define_insn "*ashrdi3_64"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-        (ashiftrt:DI (match_operand:DI 1 "register_operand" "d,d")
-                     (match_operand:SI 2 "nonmemory_operand" "J,a")))
+  [(set (match_operand:DI 0 "register_operand" "=d")
+        (ashiftrt:DI (match_operand:DI 1 "register_operand" "d")
+                     (match_operand:SI 2 "shift_count_operand" "Y")))
    (clobber (reg:CC 33))]
   "TARGET_64BIT"
-  "@
-   srag\t%0,%1,%c2
-   srag\t%0,%1,0(%2)"
+  "srag\t%0,%1,%Y2"
   [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
@@ -6142,13 +6122,11 @@
 ;
 
 (define_insn "ashlsi3"
-  [(set (match_operand:SI 0 "register_operand" "=d,d")
-        (ashift:SI (match_operand:SI 1 "register_operand" "0,0")
-                   (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:SI 0 "register_operand" "=d")
+        (ashift:SI (match_operand:SI 1 "register_operand" "0")
+                   (match_operand:SI 2 "shift_count_operand" "Y")))]
   ""
-  "@
-   sll\t%0,%c2
-   sll\t%0,0(%2)"
+  "sll\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
@@ -6158,41 +6136,35 @@
 
 (define_insn "*ashrsi3_cc"
   [(set (reg 33)
-        (compare (ashiftrt:SI (match_operand:SI 1 "register_operand" "0,0")
-                              (match_operand:SI 2 "nonmemory_operand" "J,a"))
+        (compare (ashiftrt:SI (match_operand:SI 1 "register_operand" "0")
+                              (match_operand:SI 2 "shift_count_operand" "Y"))
                  (const_int 0)))
-   (set (match_operand:SI 0 "register_operand" "=d,d")
+   (set (match_operand:SI 0 "register_operand" "=d")
         (ashiftrt:SI (match_dup 1) (match_dup 2)))]
   "s390_match_ccmode(insn, CCSmode)"
-  "@
-   sra\t%0,%c2
-   sra\t%0,0(%2)"
+  "sra\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
 
 (define_insn "*ashrsi3_cconly"
   [(set (reg 33)
-        (compare (ashiftrt:SI (match_operand:SI 1 "register_operand" "0,0")
-                              (match_operand:SI 2 "nonmemory_operand" "J,a"))
+        (compare (ashiftrt:SI (match_operand:SI 1 "register_operand" "0")
+                              (match_operand:SI 2 "shift_count_operand" "Y"))
                  (const_int 0)))
-   (clobber (match_scratch:SI 0 "=d,d"))]
+   (clobber (match_scratch:SI 0 "=d"))]
   "s390_match_ccmode(insn, CCSmode)"
-  "@
-   sra\t%0,%c2
-   sra\t%0,0(%2)"
+  "sra\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
 (define_insn "ashrsi3"
-  [(set (match_operand:SI 0 "register_operand" "=d,d")
-        (ashiftrt:SI (match_operand:SI 1 "register_operand" "0,0")
-                     (match_operand:SI 2 "nonmemory_operand" "J,a")))
+  [(set (match_operand:SI 0 "register_operand" "=d")
+        (ashiftrt:SI (match_operand:SI 1 "register_operand" "0")
+                     (match_operand:SI 2 "shift_count_operand" "Y")))
    (clobber (reg:CC 33))]
   ""
-  "@
-   sra\t%0,%c2
-   sra\t%0,0(%2)"
+  "sra\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
@@ -6208,30 +6180,26 @@
 (define_expand "lshrdi3"
   [(set (match_operand:DI 0 "register_operand" "")
         (lshiftrt:DI (match_operand:DI 1 "register_operand" "")
-                     (match_operand:SI 2 "nonmemory_operand" "")))]
+                     (match_operand:SI 2 "shift_count_operand" "")))]
   ""
   "")
 
 (define_insn "*lshrdi3_31"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-        (lshiftrt:DI (match_operand:DI 1 "register_operand" "0,0")
-                     (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:DI 0 "register_operand" "=d")
+        (lshiftrt:DI (match_operand:DI 1 "register_operand" "0")
+                     (match_operand:SI 2 "shift_count_operand" "Y")))]
   "!TARGET_64BIT"
-  "@
-   srdl\t%0,%c2
-   srdl\t%0,0(%2)"
-   [(set_attr "op_type"  "RS,RS")
+  "srdl\t%0,%Y2"
+   [(set_attr "op_type"  "RS")
     (set_attr "atype"    "reg")])
 
 (define_insn "*lshrdi3_64"
-  [(set (match_operand:DI 0 "register_operand" "=d,d")
-        (lshiftrt:DI (match_operand:DI 1 "register_operand" "d,d")
-                     (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:DI 0 "register_operand" "=d")
+        (lshiftrt:DI (match_operand:DI 1 "register_operand" "d")
+                     (match_operand:SI 2 "shift_count_operand" "Y")))]
   "TARGET_64BIT"
-  "@
-   srlg\t%0,%1,%c2
-   srlg\t%0,%1,0(%2)"
-  [(set_attr "op_type"  "RSE,RSE")
+  "srlg\t%0,%1,%Y2"
+  [(set_attr "op_type"  "RSE")
    (set_attr "atype"    "reg")])
 
 ;
@@ -6239,13 +6207,11 @@
 ;
 
 (define_insn "lshrsi3"
-  [(set (match_operand:SI 0 "register_operand" "=d,d")
-        (lshiftrt:SI (match_operand:SI 1 "register_operand" "0,0")
-                     (match_operand:SI 2 "nonmemory_operand" "J,a")))]
+  [(set (match_operand:SI 0 "register_operand" "=d")
+        (lshiftrt:SI (match_operand:SI 1 "register_operand" "0")
+                     (match_operand:SI 2 "shift_count_operand" "Y")))]
   ""
-  "@
-   srl\t%0,%c2
-   srl\t%0,0(%2)"
+  "srl\t%0,%Y2"
   [(set_attr "op_type"  "RS")
    (set_attr "atype"    "reg")])
 
-- 
GitLab