From 2cf63121e9640348fa3d917dfb247da545255c61 Mon Sep 17 00:00:00 2001
From: "Maciej W. Rozycki" <macro@imgtec.com>
Date: Tue, 15 Nov 2016 15:04:10 +0000
Subject: [PATCH] MIPS/GCC: Mark trailing labels with `.insn'

	gcc/
	* config/mips/mips.c (mips16_emit_constants): Emit `consttable'
	insn at the beginning of the constant pool.
	(mips_insert_insn_pseudos): New function.
	(mips_machine_reorg2): Call it.
	* config/mips/mips.md (unspec): Add UNSPEC_CONSTTABLE and
	UNSPEC_INSN_PSEUDO enum values.
	(insn_pseudo, consttable): New insns.

	gcc/testsuite/
	* gcc.target/mips/insn-casesi.c: New test case.
	* gcc.target/mips/insn-pseudo-1.c: New test case.
	* gcc.target/mips/insn-pseudo-2.c: New test case.
	* gcc.target/mips/insn-pseudo-3.c: New test case.
	* gcc.target/mips/insn-pseudo-4.c: New test case.
	* gcc.target/mips/insn-tablejump.c: New test case.

From-SVN: r242424
---
 gcc/ChangeLog                                 |  10 ++
 gcc/config/mips/mips.c                        |  43 +++++++
 gcc/config/mips/mips.md                       |  19 +++
 gcc/testsuite/ChangeLog                       |   9 ++
 gcc/testsuite/gcc.target/mips/insn-casesi.c   | 112 ++++++++++++++++++
 gcc/testsuite/gcc.target/mips/insn-pseudo-1.c |  23 ++++
 gcc/testsuite/gcc.target/mips/insn-pseudo-2.c |  23 ++++
 gcc/testsuite/gcc.target/mips/insn-pseudo-3.c |  23 ++++
 gcc/testsuite/gcc.target/mips/insn-pseudo-4.c |  27 +++++
 .../gcc.target/mips/insn-tablejump.c          |  98 +++++++++++++++
 10 files changed, 387 insertions(+)
 create mode 100644 gcc/testsuite/gcc.target/mips/insn-casesi.c
 create mode 100644 gcc/testsuite/gcc.target/mips/insn-pseudo-1.c
 create mode 100644 gcc/testsuite/gcc.target/mips/insn-pseudo-2.c
 create mode 100644 gcc/testsuite/gcc.target/mips/insn-pseudo-3.c
 create mode 100644 gcc/testsuite/gcc.target/mips/insn-pseudo-4.c
 create mode 100644 gcc/testsuite/gcc.target/mips/insn-tablejump.c

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index c4a660f0cff6..b91bf89652c2 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,13 @@
+2016-11-15  Maciej W. Rozycki  <macro@imgtec.com>
+
+	* config/mips/mips.c (mips16_emit_constants): Emit `consttable'
+	insn at the beginning of the constant pool.
+	(mips_insert_insn_pseudos): New function.
+	(mips_machine_reorg2): Call it.
+	* config/mips/mips.md (unspec): Add UNSPEC_CONSTTABLE and
+	UNSPEC_INSN_PSEUDO enum values.
+	(insn_pseudo, consttable): New insns.
+
 2016-11-15  Michael Matz  <matz@suse.de>
 
 	PR missed-optimization/77881
diff --git a/gcc/config/mips/mips.c b/gcc/config/mips/mips.c
index 552b73adaf74..44cdeb72c1d4 100644
--- a/gcc/config/mips/mips.c
+++ b/gcc/config/mips/mips.c
@@ -17140,6 +17140,8 @@ mips16_emit_constants (struct mips16_constant *constants, rtx_insn *insn)
   int align;
 
   align = 0;
+  if (constants)
+    insn = emit_insn_after (gen_consttable (), insn);
   for (c = constants; c != NULL; c = next)
     {
       /* If necessary, increase the alignment of PC.  */
@@ -19015,6 +19017,46 @@ mips16_split_long_branches (void)
   while (something_changed);
 }
 
+/* Insert a `.insn' assembly pseudo-op after any labels followed by
+   a MIPS16 constant pool or no insn at all.  This is needed so that
+   targets that have been optimized away are still marked as code
+   and therefore branches that remained and point to them are known
+   to retain the ISA mode and as such can be successfully assembled.  */
+
+static void
+mips_insert_insn_pseudos (void)
+{
+  bool insn_pseudo_needed = TRUE;
+  rtx_insn *insn;
+
+  for (insn = get_last_insn (); insn != NULL_RTX; insn = PREV_INSN (insn))
+    switch (GET_CODE (insn))
+      {
+      case INSN:
+	if (GET_CODE (PATTERN (insn)) == UNSPEC_VOLATILE
+	    && XINT (PATTERN (insn), 1) == UNSPEC_CONSTTABLE)
+	  {
+	    insn_pseudo_needed = TRUE;
+	    break;
+	  }
+	/* Fall through.  */
+      case JUMP_INSN:
+      case CALL_INSN:
+      case JUMP_TABLE_DATA:
+	insn_pseudo_needed = FALSE;
+	break;
+      case CODE_LABEL:
+	if (insn_pseudo_needed)
+	  {
+	    emit_insn_after (gen_insn_pseudo (), insn);
+	    insn_pseudo_needed = FALSE;
+	  }
+	break;
+      default:
+	break;
+      }
+}
+
 /* Implement TARGET_MACHINE_DEPENDENT_REORG.  */
 
 static void
@@ -19050,6 +19092,7 @@ mips_machine_reorg2 (void)
        optimizations, but this should be an extremely rare case anyhow.  */
     mips_reorg_process_insns ();
   mips16_split_long_branches ();
+  mips_insert_insn_pseudos ();
   return 0;
 }
 
diff --git a/gcc/config/mips/mips.md b/gcc/config/mips/mips.md
index d8d564fabd9c..b7e8e96820d7 100644
--- a/gcc/config/mips/mips.md
+++ b/gcc/config/mips/mips.md
@@ -120,6 +120,7 @@
 
   ;; MIPS16 constant pools.
   UNSPEC_ALIGN
+  UNSPEC_CONSTTABLE
   UNSPEC_CONSTTABLE_INT
   UNSPEC_CONSTTABLE_FLOAT
 
@@ -151,6 +152,9 @@
 
   ;; Stack checking.
   UNSPEC_PROBE_STACK_RANGE
+
+  ;; The `.insn' pseudo-op.
+  UNSPEC_INSN_PSEUDO
 ])
 
 (define_constants
@@ -7174,6 +7178,14 @@
       return "#nop";
   }
   [(set_attr "type"	"nop")])
+
+;; The `.insn' pseudo-op.
+(define_insn "insn_pseudo"
+  [(unspec_volatile [(const_int 0)] UNSPEC_INSN_PSEUDO)]
+  ""
+  ".insn"
+  [(set_attr "mode" "none")
+   (set_attr "insn_count" "0")])
 
 ;; MIPS4 Conditional move instructions.
 
@@ -7308,6 +7320,13 @@
 ;;  ....................
 ;;
 
+(define_insn "consttable"
+  [(unspec_volatile [(const_int 0)] UNSPEC_CONSTTABLE)]
+  ""
+  ""
+  [(set_attr "mode" "none")
+   (set_attr "insn_count" "0")])
+
 (define_insn "consttable_tls_reloc"
   [(unspec_volatile [(match_operand 0 "tls_reloc_operand" "")
 		     (match_operand 1 "const_int_operand" "")]
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index e7e78506ef22..e0c99bf50a2d 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,12 @@
+2016-11-15  Maciej W. Rozycki  <macro@imgtec.com>
+
+	* gcc.target/mips/insn-casesi.c: New test case.
+	* gcc.target/mips/insn-pseudo-1.c: New test case.
+	* gcc.target/mips/insn-pseudo-2.c: New test case.
+	* gcc.target/mips/insn-pseudo-3.c: New test case.
+	* gcc.target/mips/insn-pseudo-4.c: New test case.
+	* gcc.target/mips/insn-tablejump.c: New test case.
+
 2016-11-15  Maciej W. Rozycki  <macro@imgtec.com>
 
 	* gcc.target/mips/mips.exp (mips_option_tests): Add
diff --git a/gcc/testsuite/gcc.target/mips/insn-casesi.c b/gcc/testsuite/gcc.target/mips/insn-casesi.c
new file mode 100644
index 000000000000..2b4c9f21986f
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/insn-casesi.c
@@ -0,0 +1,112 @@
+/* { dg-do run } */
+/* { dg-options "-mips16 -mcode-readable=yes" } */
+
+int __attribute__ ((noinline))
+frob (int i)
+{
+  switch (i)
+    {
+    case -5:
+      return -2;
+    case -3:
+      return -1;
+    case 0:
+      return 0;
+    case 3:
+      return 1;
+    case 5:
+      break;
+    default:
+      __builtin_unreachable ();
+    }
+  return i;
+}
+
+int
+main (int argc, char **argv)
+{
+  asm ("" : "+r" (argc));
+  argc = frob ((argc & 10) - 5);
+  asm ("" : "+r" (argc));
+  return !argc;
+}
+
+/* This will result in assembly like:
+
+	.text
+	.align	2
+	.globl	frob
+	.set	mips16
+	.set	nomicromips
+	.ent	frob
+	.type	frob, @function
+frob:
+	.frame	$sp,0,$31		# vars= 0, regs= 0/0, args= 0, gp= 0
+	.mask	0x00000000,0
+	.fmask	0x00000000,0
+	addiu	$2,$4,5
+	sltu	$2,11
+	bteqz	$L2
+	sll	$3,$2,1
+	la	$2,$L4
+	addu	$3,$2,$3
+	lh	$3,0($3)
+	addu	$2,$2,$3
+	j	$2
+	.align	1
+	.align	2
+$L4:
+	.half	$L3-$L4
+	.half	$L2-$L4
+	.half	$L9-$L4
+	.half	$L2-$L4
+	.half	$L2-$L4
+	.half	$L8-$L4
+	.half	$L2-$L4
+	.half	$L2-$L4
+	.half	$L7-$L4
+	.half	$L2-$L4
+	.half	$L8-$L4
+$L8:
+	.set	noreorder
+	.set	nomacro
+	jr	$31
+	move	$2,$4
+	.set	macro
+	.set	reorder
+
+$L9:
+	li	$2,1
+	.set	noreorder
+	.set	nomacro
+	jr	$31
+	neg	$2,$2
+	.set	macro
+	.set	reorder
+
+$L3:
+	li	$2,2
+	.set	noreorder
+	.set	nomacro
+	jr	$31
+	neg	$2,$2
+	.set	macro
+	.set	reorder
+
+$L7:
+	.set	noreorder
+	.set	nomacro
+	jr	$31
+	li	$2,1
+	.set	macro
+	.set	reorder
+
+$L2:
+	.insn
+	.end	frob
+	.size	frob, .-frob
+
+  for `frob' and we want to make sure it links correctly owing to the
+  `.insn' pseudo-op which needs to be there at `$L2' as there's no
+  code following and the label is a MIPS16 branch target (even though
+  the branch is never taken.  See also insn-tablejump.c.  */
diff --git a/gcc/testsuite/gcc.target/mips/insn-pseudo-1.c b/gcc/testsuite/gcc.target/mips/insn-pseudo-1.c
new file mode 100644
index 000000000000..42501952f9ce
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/insn-pseudo-1.c
@@ -0,0 +1,23 @@
+/* { dg-do compile } */
+/* { dg-options "-mno-micromips -mno-mips16" } */
+
+void
+unreachable (int i)
+{
+  asm volatile goto ("b\t.\n\tbeqz\t%0,%l1" : : "r" (i) : : punt);
+punt:
+  __builtin_unreachable ();
+}
+
+/* Expect assembly like:
+
+	beqz	$4,$L2
+				# Anything goes here.
+$L2:				# The label must match.
+	.insn
+$L3 = .				# It's there, but we don't care.
+	.end	unreachable
+
+   that is .insn to be inserted if a code label is at function's end.  */
+
+/* { dg-final { scan-assembler "\tbeqz\t\\\$\[0-9\]+,(.L\[0-9\]+)\n.*\n\\1:\n\t\\.insn\n(?:.L\[0-9\]+ = \\.\n)?\t\\.end\tunreachable\n" } } */
diff --git a/gcc/testsuite/gcc.target/mips/insn-pseudo-2.c b/gcc/testsuite/gcc.target/mips/insn-pseudo-2.c
new file mode 100644
index 000000000000..81fb25962308
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/insn-pseudo-2.c
@@ -0,0 +1,23 @@
+/* { dg-do compile } */
+/* { dg-options "-mmicromips" } */
+
+void
+unreachable (int i)
+{
+  asm volatile goto ("b\t.\n\tbeqz\t%0,%l1" : : "r" (i) : : punt);
+punt:
+  __builtin_unreachable ();
+}
+
+/* Expect assembly like:
+
+	beqz	$4,$L2
+				# Anything goes here.
+$L2:				# The label must match.
+	.insn
+$L3 = .				# It's there, but we don't care.
+	.end	unreachable
+
+   that is .insn to be inserted if a code label is at function's end.  */
+
+/* { dg-final { scan-assembler "\tbeqz\t\\\$\[0-9\]+,(.L\[0-9\]+)\n.*\n\\1:\n\t\\.insn\n(?:.L\[0-9\]+ = \\.\n)?\t\\.end\tunreachable\n" } } */
diff --git a/gcc/testsuite/gcc.target/mips/insn-pseudo-3.c b/gcc/testsuite/gcc.target/mips/insn-pseudo-3.c
new file mode 100644
index 000000000000..49b7622ba788
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/insn-pseudo-3.c
@@ -0,0 +1,23 @@
+/* { dg-do compile } */
+/* { dg-options "-mips16" } */
+
+void
+unreachable (int i)
+{
+  asm volatile goto ("b\t.\n\tbeqz\t%0,%l1" : : "r" (i) : : punt);
+punt:
+  __builtin_unreachable ();
+}
+
+/* Expect assembly like:
+
+	beqz	$4,$L2
+				# Anything goes here.
+$L2:				# The label must match.
+	.insn
+$L3 = .				# It's there, but we don't care.
+	.end	unreachable
+
+   that is .insn to be inserted if a code label is at function's end.  */
+
+/* { dg-final { scan-assembler "\tbeqz\t\\\$\[0-9\]+,(.L\[0-9\]+)\n.*\n\\1:\n\t\\.insn\n(?:.L\[0-9\]+ = \\.\n)?\t\\.end\tunreachable\n" } } */
diff --git a/gcc/testsuite/gcc.target/mips/insn-pseudo-4.c b/gcc/testsuite/gcc.target/mips/insn-pseudo-4.c
new file mode 100644
index 000000000000..49a485191616
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/insn-pseudo-4.c
@@ -0,0 +1,27 @@
+/* { dg-do compile } */
+/* { dg-options "-mips16 -mcode-readable=yes" } */
+
+void
+unreachable (void)
+{
+  asm volatile goto ("b\t.\n\tbeqz\t%0,%l1" : : "r" (0x12345678) : : punt);
+punt:
+  __builtin_unreachable ();
+}
+
+/* Expect assembly like:
+
+	lw	$2,$L5
+				# Anything goes here.
+	beqz	$2,$L2		# The register must match.
+				# Anything goes here.
+$L2:				# The label must match.
+	.insn
+$L3 = .				# It's there, but we don't care.
+	.align	2
+$L5:				# The label must match.
+	.word	305419896
+
+   that is .insn to be inserted if a code label is at a constant pool.  */
+
+/* { dg-final { scan-assembler "\tlw\t(\\\$\[0-9\]+),(.L\[0-9\]+)\n.*\tbeqz\t\\1,(.L\[0-9\]+)\n.*\n\\3:\n\t\\.insn\n(?:.L\[0-9\]+ = \\.\n)?\t\\.align\t2\n\\2:\n\t\\.word\t305419896\n" } } */
diff --git a/gcc/testsuite/gcc.target/mips/insn-tablejump.c b/gcc/testsuite/gcc.target/mips/insn-tablejump.c
new file mode 100644
index 000000000000..ecba154b9e04
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/insn-tablejump.c
@@ -0,0 +1,98 @@
+/* { dg-do run } */
+/* { dg-options "-mmicromips" } */
+
+int __attribute__ ((noinline))
+frob (int i)
+{
+  switch (i)
+    {
+    case -5:
+      return -2;
+    case -3:
+      return -1;
+    case 0:
+      return 0;
+    case 3:
+      return 1;
+    case 5:
+      break;
+    default:
+      __builtin_unreachable ();
+    }
+  return i;
+}
+
+int
+main (int argc, char **argv)
+{
+  asm ("" : "+r" (argc));
+  argc = frob ((argc & 10) - 5);
+  asm ("" : "+r" (argc));
+  return !argc;
+}
+
+/* This will result in assembly like:
+
+	.text
+	.align	2
+	.globl	frob
+	.set	nomips16
+	.set	micromips
+	.ent	frob
+	.type	frob, @function
+frob:
+	.frame	$sp,0,$31		# vars= 0, regs= 0/0, args= 0, gp= 0
+	.mask	0x00000000,0
+	.fmask	0x00000000,0
+	.set	noreorder
+	.set	nomacro
+	addiu	$3,$4,5
+	sltu	$2,$3,11
+	beqzc	$2,$L2
+	lui	$2,%hi($L4)
+	addiu	$2,$2,%lo($L4)
+	lwxs	$3,$3($2)
+	jrc	$3
+	.rdata
+	.align	2
+	.align	2
+$L4:
+	.word	$L3
+	.word	$L2
+	.word	$L9
+	.word	$L2
+	.word	$L2
+	.word	$L8
+	.word	$L2
+	.word	$L2
+	.word	$L7
+	.word	$L2
+	.word	$L8
+	.text
+$L8:
+	jr	$31
+	move	$2,$4
+
+$L9:
+	jr	$31
+	li	$2,-1			# 0xffffffffffffffff
+
+$L3:
+	jr	$31
+	li	$2,-2			# 0xfffffffffffffffe
+
+$L7:
+	jr	$31
+	li	$2,1			# 0x1
+
+$L2:
+	.insn
+	.set	macro
+	.set	reorder
+	.end	frob
+	.size	frob, .-frob
+
+  for `frob' and we want to make sure it links correctly owing to the
+  `.insn' pseudo-op which needs to be there at `$L2' as there's no
+  code following and the label is a microMIPS branch target (even though
+  the branch is never taken.  See also insn-casesi.c.  */
-- 
GitLab