diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 8fc34d64d95001f026dd2b3902ae817f5cb43ddb..843c4460ffb0cd457ea834e9cb955e9c3f833eb5 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,49 @@
+2011-11-27  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	* config/mips/mips-protos.h (mips_emit_binary): Declare.
+	* config/mips/mips.c (mips_emit_binary): Make global.
+	(mips_set_mips16_mode): Turn off -mfix-r4000 in MIPS16 mode.
+	(mips_conditional_register_usage): Don't treat LO and HI as
+	register operands in MIPS16 mode.
+	(mips_mulsidi3_gen_fn): Use {u,}mulsidi3_{32,64}bit_mips16
+	for MIPS16 code.
+	* config/mips/predicates.md (muldiv_target_operand): New predicate.
+	(move_operand): Allow hilo_operand.
+	* config/mips/mips.md (mul<mode>3): Explicitly specify LO as the
+	target of MIPS16 multiplies, then move it into the target register.
+	(mul<mode>3_internal, *macc2, *msac2): Use muldiv_target_operand.
+	(<u>mulsidi3_32bit_mips16): New expander.
+	(<u>mulsidi3_32bit): Use muldiv_target_operand.
+	(<u>mulsidi3_32bit_r4000): Disable for ISA_HAS_DSP.
+	(<u>mulsidi3_64bit): Require !TARGET_MIPS16.  Split into
+	<u>mulsidi3_64bit_split.
+	(<u>mulsidi3_64bit_mips16): New expander.
+	(<u>mulsidi3_64bit_split): Likewise, using expansions from
+	two previous define_splits.
+	(<u>mulsidi3_64bit_hilo, *muls<u>_di, <u>msubsidi4): Use
+	muldiv_target_operand.
+	(<su>mulsi3_highpart): Use <su>mulsi3_highpart_split for MIPS16 code.
+	(<su>mulsi3_highpart_internal): Require !TARGET_MIPS16.
+	Split into <su>mulsi3_highpart_split.
+	(<su>mulsi3_highpart_split): New expander.
+	(<su>muldi3_highpart): Turn into a define_expand.
+	Use <su>muldi3_highpart_split for MIPS16 code.
+	(<su>muldi3_highpart_internal): Renamed from <su>muldi3_highpart.
+	Require !TARGET_MIPS16.  Split into <su>muldi3_highpart_split.
+	(<su>muldi3_highpart_split): New expander.
+	(<u>mulditi3): Explicitly specify LO as the target of MIPS16
+	multiplies, then move it into the target register.
+	(<u>mulditi3_internal, <u>maddsidi4): Use muldiv_target_operand.
+	(divmod<mode>4, udivmod<mode>4): Turn into define_expands.
+	Use <u>divmod<mode>4_split for MIPS16 code, then explicitly
+	move LO into operand 0.
+	(divmod<mode>4_internal, udivmod<mode>4_internal): Renamed
+	from <u>divmod<mode>4.  Use muldiv_target_operand.
+	Require !TARGET_MIPS16.  Split into <u>divmod<mode>4_split.
+	(<u>divmod<mode>4_split): New expander.
+	(<u>divmod<GPR:mode>4_hilo_<HILO:mode>): Use muldiv_target_operand.
+	(mfhi<GPR:mode>_<HILO:mode>): Use hilo_operand.
+
 2011-11-27  Richard Sandiford  <rdsandiford@googlemail.com>
 
 	* hard-reg-set.h (target_hard_regs): Add x_accessible_reg_set
diff --git a/gcc/config/mips/mips-protos.h b/gcc/config/mips/mips-protos.h
index b28b0b391656c8ddf589170444a0a2f826c0439a..dbabdffaef08c6b9b1ddf63d00448ec1ac039080 100644
--- a/gcc/config/mips/mips-protos.h
+++ b/gcc/config/mips/mips-protos.h
@@ -191,6 +191,9 @@ extern int mips_split_const_insns (rtx);
 extern int mips_load_store_insns (rtx, rtx);
 extern int mips_idiv_insns (void);
 extern rtx mips_emit_move (rtx, rtx);
+#ifdef RTX_CODE
+extern void mips_emit_binary (enum rtx_code, rtx, rtx, rtx);
+#endif
 extern rtx mips_pic_base_register (rtx);
 extern rtx mips_got_load (rtx, rtx, enum mips_symbol_type);
 extern bool mips_split_symbol (rtx, rtx, enum machine_mode, rtx *);
diff --git a/gcc/config/mips/mips.c b/gcc/config/mips/mips.c
index ea971a91d9cd4bc39e8507b0b298fff8c333603d..3fe91cd1e3e4f7b56a3cad6d2962cb5924f32e62 100644
--- a/gcc/config/mips/mips.c
+++ b/gcc/config/mips/mips.c
@@ -2398,7 +2398,7 @@ mips_force_unary (enum machine_mode mode, enum rtx_code code, rtx op0)
 
 /* Emit an instruction of the form (set TARGET (CODE OP0 OP1)).  */
 
-static void
+void
 mips_emit_binary (enum rtx_code code, rtx target, rtx op0, rtx op1)
 {
   emit_insn (gen_rtx_SET (VOIDmode, target,
@@ -15250,6 +15250,11 @@ mips_set_mips16_mode (int mips16_p)
       /* MIPS16 has no BAL instruction.  */
       target_flags &= ~MASK_RELAX_PIC_CALLS;
 
+      /* The R4000 errata don't apply to any known MIPS16 cores.
+	 It's simpler to make the R4000 fixes and MIPS16 mode
+	 mutually exclusive.  */
+      target_flags &= ~MASK_FIX_R4000;
+
       if (flag_pic && !TARGET_OLDABI)
 	sorry ("MIPS16 PIC for ABIs other than o32 and o64");
 
@@ -15856,12 +15861,12 @@ mips_conditional_register_usage (void)
       SET_HARD_REG_BIT (accessible_reg_set, FPSW_REGNUM);
       fixed_regs[FPSW_REGNUM] = call_used_regs[FPSW_REGNUM] = 1;
     }
-  /* In MIPS16 mode, we permit the $t temporary registers to be used
-     for reload.  We prohibit the unused $s registers, since they
-     are call-saved, and saving them via a MIPS16 register would
-     probably waste more time than just reloading the value.  */
   if (TARGET_MIPS16)
     {
+      /* In MIPS16 mode, we permit the $t temporary registers to be used
+	 for reload.  We prohibit the unused $s registers, since they
+	 are call-saved, and saving them via a MIPS16 register would
+	 probably waste more time than just reloading the value.  */
       fixed_regs[18] = call_used_regs[18] = 1;
       fixed_regs[19] = call_used_regs[19] = 1;
       fixed_regs[20] = call_used_regs[20] = 1;
@@ -15871,6 +15876,12 @@ mips_conditional_register_usage (void)
       fixed_regs[26] = call_used_regs[26] = 1;
       fixed_regs[27] = call_used_regs[27] = 1;
       fixed_regs[30] = call_used_regs[30] = 1;
+
+      /* Do not allow HI and LO to be treated as register operands.
+	 There are no MTHI or MTLO instructions (or any real need
+	 for them) and one-way registers cannot easily be reloaded.  */
+      AND_COMPL_HARD_REG_SET (operand_reg_set,
+			      reg_class_contents[(int) MD_REGS]);
     }
   /* $f20-$f23 are call-clobbered for n64.  */
   if (mips_abi == ABI_64)
@@ -16056,12 +16067,20 @@ mips_mulsidi3_gen_fn (enum rtx_code ext_code)
 	 case we still expand mulsidi3 for DMUL.  */
       if (ISA_HAS_DMUL3)
 	return signed_p ? gen_mulsidi3_64bit_dmul : NULL;
+      if (TARGET_MIPS16)
+	return (signed_p
+		? gen_mulsidi3_64bit_mips16
+		: gen_umulsidi3_64bit_mips16);
       if (TARGET_FIX_R4000)
 	return NULL;
       return signed_p ? gen_mulsidi3_64bit : gen_umulsidi3_64bit;
     }
   else
     {
+      if (TARGET_MIPS16)
+	return (signed_p
+		? gen_mulsidi3_32bit_mips16
+		: gen_umulsidi3_32bit_mips16);
       if (TARGET_FIX_R4000 && !ISA_HAS_DSP)
 	return signed_p ? gen_mulsidi3_32bit_r4000 : gen_umulsidi3_32bit_r4000;
       return signed_p ? gen_mulsidi3_32bit : gen_umulsidi3_32bit;
diff --git a/gcc/config/mips/mips.md b/gcc/config/mips/mips.md
index c2211a3c170855d5fe03cf98cf5d549a84d8d0fc..55b7fffb6659eef9d7ac0cfa13a3f801a9996ebf 100644
--- a/gcc/config/mips/mips.md
+++ b/gcc/config/mips/mips.md
@@ -1331,11 +1331,19 @@
 		  (match_operand:GPR 2 "register_operand")))]
   ""
 {
+  rtx lo;
+
   if (TARGET_LOONGSON_2EF || TARGET_LOONGSON_3A)
     emit_insn (gen_mul<mode>3_mul3_loongson (operands[0], operands[1],
                                              operands[2]));
   else if (ISA_HAS_<D>MUL3)
     emit_insn (gen_mul<mode>3_mul3 (operands[0], operands[1], operands[2]));
+  else if (TARGET_MIPS16)
+    {
+      lo = gen_rtx_REG (<MODE>mode, LO_REGNUM);
+      emit_insn (gen_mul<mode>3_internal (lo, operands[1], operands[2]));
+      emit_move_insn (operands[0], lo);
+    }
   else if (TARGET_FIX_R4000)
     emit_insn (gen_mul<mode>3_r4000 (operands[0], operands[1], operands[2]));
   else
@@ -1398,7 +1406,7 @@
         (clobber (match_dup 0))])])
 
 (define_insn "mul<mode>3_internal"
-  [(set (match_operand:GPR 0 "register_operand" "=l")
+  [(set (match_operand:GPR 0 "muldiv_target_operand" "=l")
 	(mult:GPR (match_operand:GPR 1 "register_operand" "d")
 		  (match_operand:GPR 2 "register_operand" "d")))]
   "!TARGET_FIX_R4000"
@@ -1575,7 +1583,7 @@
 ;; Patterns generated by the define_peephole2 below.
 
 (define_insn "*macc2"
-  [(set (match_operand:SI 0 "register_operand" "=l")
+  [(set (match_operand:SI 0 "muldiv_target_operand" "=l")
 	(plus:SI (mult:SI (match_operand:SI 1 "register_operand" "d")
 			  (match_operand:SI 2 "register_operand" "d"))
 		 (match_dup 0)))
@@ -1589,7 +1597,7 @@
    (set_attr "mode"	"SI")])
 
 (define_insn "*msac2"
-  [(set (match_operand:SI 0 "register_operand" "=l")
+  [(set (match_operand:SI 0 "muldiv_target_operand" "=l")
 	(minus:SI (match_dup 0)
 		  (mult:SI (match_operand:SI 1 "register_operand" "d")
 			   (match_operand:SI 2 "register_operand" "d"))))
@@ -1744,11 +1752,25 @@
   DONE;
 })
 
+(define_expand "<u>mulsidi3_32bit_mips16"
+  [(set (match_operand:DI 0 "register_operand")
+	(mult:DI (any_extend:DI (match_operand:SI 1 "register_operand"))
+		 (any_extend:DI (match_operand:SI 2 "register_operand"))))]
+  "!TARGET_64BIT && TARGET_MIPS16"
+{
+  rtx hilo;
+
+  hilo = gen_rtx_REG (DImode, MD_REG_FIRST);
+  emit_insn (gen_<u>mulsidi3_32bit (hilo, operands[1], operands[2]));
+  emit_move_insn (operands[0], hilo);
+  DONE;
+})
+
 ;; As well as being named patterns, these instructions are used by the
 ;; __builtin_mips_mult<u>() functions.  We must always make those functions
 ;; available if !TARGET_64BIT && ISA_HAS_DSP.
 (define_insn "<u>mulsidi3_32bit"
-  [(set (match_operand:DI 0 "register_operand" "=ka")
+  [(set (match_operand:DI 0 "muldiv_target_operand" "=ka")
 	(mult:DI (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
 		 (any_extend:DI (match_operand:SI 2 "register_operand" "d"))))]
   "!TARGET_64BIT && (!TARGET_FIX_R4000 || ISA_HAS_DSP)"
@@ -1766,20 +1788,27 @@
 	(mult:DI (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
 		 (any_extend:DI (match_operand:SI 2 "register_operand" "d"))))
    (clobber (match_scratch:DI 3 "=x"))]
-  "!TARGET_64BIT && TARGET_FIX_R4000"
+  "!TARGET_64BIT && TARGET_FIX_R4000 && !ISA_HAS_DSP"
   "mult<u>\t%1,%2\;mflo\t%L0\;mfhi\t%M0"
   [(set_attr "type" "imul")
    (set_attr "mode" "SI")
    (set_attr "length" "12")])
 
-(define_insn "<u>mulsidi3_64bit"
+(define_insn_and_split "<u>mulsidi3_64bit"
   [(set (match_operand:DI 0 "register_operand" "=d")
 	(mult:DI (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
 		 (any_extend:DI (match_operand:SI 2 "register_operand" "d"))))
    (clobber (match_scratch:TI 3 "=x"))
    (clobber (match_scratch:DI 4 "=d"))]
-  "TARGET_64BIT && !TARGET_FIX_R4000 && !ISA_HAS_DMUL3"
+  "TARGET_64BIT && !TARGET_FIX_R4000 && !ISA_HAS_DMUL3 && !TARGET_MIPS16"
   "#"
+  "&& reload_completed"
+  [(const_int 0)]
+{
+  emit_insn (gen_<u>mulsidi3_64bit_split (operands[0], operands[1],
+					  operands[2], operands[4]));
+  DONE;
+}
   [(set_attr "type" "imul")
    (set_attr "mode" "SI")
    (set (attr "length")
@@ -1787,63 +1816,52 @@
 		      (const_int 16)
 		      (const_int 28)))])
 
-(define_split
-  [(set (match_operand:DI 0 "d_operand")
-	(mult:DI (any_extend:DI (match_operand:SI 1 "d_operand"))
-		 (any_extend:DI (match_operand:SI 2 "d_operand"))))
-   (clobber (match_operand:TI 3 "hilo_operand"))
-   (clobber (match_operand:DI 4 "d_operand"))]
-  "TARGET_64BIT && !TARGET_FIX_R4000 && ISA_HAS_EXT_INS && reload_completed"
-  [(set (match_dup 3)
-	(unspec:TI [(mult:DI (any_extend:DI (match_dup 1))
-			     (any_extend:DI (match_dup 2)))]
-		   UNSPEC_SET_HILO))
-
-   ;; OP0 <- LO, OP4 <- HI
-   (set (match_dup 0) (match_dup 5))
-   (set (match_dup 4) (unspec:DI [(match_dup 3)] UNSPEC_MFHI))
-
-   (set (zero_extract:DI (match_dup 0) (const_int 32) (const_int 32))
-	(match_dup 4))]
-  { operands[5] = gen_rtx_REG (DImode, LO_REGNUM); })
+(define_expand "<u>mulsidi3_64bit_mips16"
+  [(set (match_operand:DI 0 "register_operand")
+	(mult:DI (any_extend:DI (match_operand:SI 1 "register_operand"))
+		 (any_extend:DI (match_operand:SI 2 "register_operand"))))]
+  "TARGET_64BIT && TARGET_MIPS16"
+{
+  emit_insn (gen_<u>mulsidi3_64bit_split (operands[0], operands[1],
+					  operands[2], gen_reg_rtx (DImode)));
+  DONE;
+})
 
-(define_split
-  [(set (match_operand:DI 0 "d_operand")
-	(mult:DI (any_extend:DI (match_operand:SI 1 "d_operand"))
-		 (any_extend:DI (match_operand:SI 2 "d_operand"))))
-   (clobber (match_operand:TI 3 "hilo_operand"))
-   (clobber (match_operand:DI 4 "d_operand"))]
-  "TARGET_64BIT && !TARGET_FIX_R4000 && !ISA_HAS_EXT_INS && reload_completed"
-  [(set (match_dup 3)
-	(unspec:TI [(mult:DI (any_extend:DI (match_dup 1))
-			     (any_extend:DI (match_dup 2)))]
-		   UNSPEC_SET_HILO))
-
-   ;; OP0 <- LO, OP4 <- HI
-   (set (match_dup 0) (match_dup 5))
-   (set (match_dup 4) (unspec:DI [(match_dup 3)] UNSPEC_MFHI))
-
-   ;; Zero-extend OP0.
-   (set (match_dup 0)
-	(ashift:DI (match_dup 0)
-		   (const_int 32)))
-   (set (match_dup 0)
-	(lshiftrt:DI (match_dup 0)
-		     (const_int 32)))
+(define_expand "<u>mulsidi3_64bit_split"
+  [(set (match_operand:DI 0 "register_operand")
+	(mult:DI (any_extend:DI (match_operand:SI 1 "register_operand"))
+		 (any_extend:DI (match_operand:SI 2 "register_operand"))))
+   (clobber (match_operand:DI 3 "register_operand"))]
+  ""
+{
+  rtx hilo;
 
-   ;; Shift OP4 into place.
-   (set (match_dup 4)
-	(ashift:DI (match_dup 4)
-		   (const_int 32)))
+  hilo = gen_rtx_REG (TImode, MD_REG_FIRST);
+  emit_insn (gen_<u>mulsidi3_64bit_hilo (hilo, operands[1], operands[2]));
 
-   ;; OR the two halves together
-   (set (match_dup 0)
-	(ior:DI (match_dup 0)
-		(match_dup 4)))]
-  { operands[5] = gen_rtx_REG (DImode, LO_REGNUM); })
+  emit_move_insn (operands[0], gen_rtx_REG (DImode, LO_REGNUM));
+  emit_insn (gen_mfhidi_ti (operands[3], hilo));
+
+  if (ISA_HAS_EXT_INS)
+    emit_insn (gen_insvdi (operands[0], GEN_INT (32), GEN_INT (32),
+			   operands[3]));
+  else
+    {
+      /* Zero-extend the low part.  */
+      mips_emit_binary (ASHIFT, operands[0], operands[0], GEN_INT (32));
+      mips_emit_binary (LSHIFTRT, operands[0], operands[0], GEN_INT (32));
+
+      /* Shift the high part into place.  */
+      mips_emit_binary (ASHIFT, operands[3], operands[3], GEN_INT (32));
+
+      /* OR the two halves together.  */
+      mips_emit_binary (IOR, operands[0], operands[0], operands[3]);
+    }
+  DONE;
+})
 
 (define_insn "<u>mulsidi3_64bit_hilo"
-  [(set (match_operand:TI 0 "register_operand" "=x")
+  [(set (match_operand:TI 0 "muldiv_target_operand" "=x")
 	(unspec:TI
 	  [(mult:DI
 	     (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
@@ -1867,7 +1885,7 @@
 
 ;; Widening multiply with negation.
 (define_insn "*muls<u>_di"
-  [(set (match_operand:DI 0 "register_operand" "=x")
+  [(set (match_operand:DI 0 "muldiv_target_operand" "=x")
         (neg:DI
 	 (mult:DI
 	  (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
@@ -1885,9 +1903,9 @@
 ;; in GENERATE_MADD_MSUB for -mno-dsp, but always ignore them for -mdsp,
 ;; even if !ISA_HAS_DSP_MULT.
 (define_insn "<u>msubsidi4"
-  [(set (match_operand:DI 0 "register_operand" "=ka")
+  [(set (match_operand:DI 0 "muldiv_target_operand" "=ka")
         (minus:DI
-	   (match_operand:DI 3 "register_operand" "0")
+	   (match_operand:DI 3 "muldiv_target_operand" "0")
 	   (mult:DI
 	      (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
 	      (any_extend:DI (match_operand:SI 2 "register_operand" "d")))))]
@@ -1918,6 +1936,9 @@
     emit_insn (gen_<su>mulsi3_highpart_mulhi_internal (operands[0],
 						       operands[1],
 						       operands[2]));
+  else if (TARGET_MIPS16)
+    emit_insn (gen_<su>mulsi3_highpart_split (operands[0], operands[1],
+					      operands[2]));
   else
     emit_insn (gen_<su>mulsi3_highpart_internal (operands[0], operands[1],
 					         operands[2]));
@@ -1932,10 +1953,27 @@
 		   (any_extend:DI (match_operand:SI 2 "register_operand" "d")))
 	  (const_int 32))))
    (clobber (match_scratch:SI 3 "=l"))]
-  "!ISA_HAS_MULHI"
+  "!ISA_HAS_MULHI && !TARGET_MIPS16"
   { return TARGET_FIX_R4000 ? "mult<u>\t%1,%2\n\tmfhi\t%0" : "#"; }
   "&& reload_completed && !TARGET_FIX_R4000"
   [(const_int 0)]
+{
+  emit_insn (gen_<su>mulsi3_highpart_split (operands[0], operands[1],
+					    operands[2]));
+  DONE;
+}
+  [(set_attr "type" "imul")
+   (set_attr "mode" "SI")
+   (set_attr "length" "8")])
+
+(define_expand "<su>mulsi3_highpart_split"
+  [(set (match_operand:SI 0 "register_operand")
+	(truncate:SI
+	 (lshiftrt:DI
+	  (mult:DI (any_extend:DI (match_operand:SI 1 "register_operand"))
+		   (any_extend:DI (match_operand:SI 2 "register_operand")))
+	  (const_int 32))))]
+  ""
 {
   rtx hilo;
 
@@ -1952,10 +1990,7 @@
       emit_insn (gen_mfhisi_di (operands[0], hilo));
     }
   DONE;
-}
-  [(set_attr "type" "imul")
-   (set_attr "mode" "SI")
-   (set_attr "length" "8")])
+})
 
 (define_insn "<su>mulsi3_highpart_mulhi_internal"
   [(set (match_operand:SI 0 "register_operand" "=d")
@@ -1989,7 +2024,25 @@
 ;; Disable unsigned multiplication for -mfix-vr4120.  This is for VR4120
 ;; errata MD(0), which says that dmultu does not always produce the
 ;; correct result.
-(define_insn_and_split "<su>muldi3_highpart"
+(define_expand "<su>muldi3_highpart"
+  [(set (match_operand:DI 0 "register_operand")
+	(truncate:DI
+	 (lshiftrt:TI
+	  (mult:TI (any_extend:TI (match_operand:DI 1 "register_operand"))
+		   (any_extend:TI (match_operand:DI 2 "register_operand")))
+	  (const_int 64))))]
+  "TARGET_64BIT && !(<CODE> == ZERO_EXTEND && TARGET_FIX_VR4120)"
+{
+  if (TARGET_MIPS16)
+    emit_insn (gen_<su>muldi3_highpart_split (operands[0], operands[1],
+					      operands[2]));
+  else
+    emit_insn (gen_<su>muldi3_highpart_internal (operands[0], operands[1],
+						 operands[2]));
+  DONE;
+})
+
+(define_insn_and_split "<su>muldi3_highpart_internal"
   [(set (match_operand:DI 0 "register_operand" "=d")
 	(truncate:DI
 	 (lshiftrt:TI
@@ -1997,10 +2050,29 @@
 		   (any_extend:TI (match_operand:DI 2 "register_operand" "d")))
 	  (const_int 64))))
    (clobber (match_scratch:DI 3 "=l"))]
-  "TARGET_64BIT && !(<CODE> == ZERO_EXTEND && TARGET_FIX_VR4120)"
+  "TARGET_64BIT
+   && !TARGET_MIPS16
+   && !(<CODE> == ZERO_EXTEND && TARGET_FIX_VR4120)"
   { return TARGET_FIX_R4000 ? "dmult<u>\t%1,%2\n\tmfhi\t%0" : "#"; }
   "&& reload_completed && !TARGET_FIX_R4000"
   [(const_int 0)]
+{
+  emit_insn (gen_<su>muldi3_highpart_split (operands[0], operands[1],
+					    operands[2]));
+  DONE;
+}
+  [(set_attr "type" "imul")
+   (set_attr "mode" "DI")
+   (set_attr "length" "8")])
+
+(define_expand "<su>muldi3_highpart_split"
+  [(set (match_operand:DI 0 "register_operand")
+	(truncate:DI
+	 (lshiftrt:TI
+	  (mult:TI (any_extend:TI (match_operand:DI 1 "register_operand"))
+		   (any_extend:TI (match_operand:DI 2 "register_operand")))
+	  (const_int 64))))]
+  ""
 {
   rtx hilo;
 
@@ -2008,10 +2080,7 @@
   emit_insn (gen_<u>mulditi3_internal (hilo, operands[1], operands[2]));
   emit_insn (gen_mfhidi_ti (operands[0], hilo));
   DONE;
-}
-  [(set_attr "type" "imul")
-   (set_attr "mode" "DI")
-   (set_attr "length" "8")])
+})
 
 (define_expand "<u>mulditi3"
   [(set (match_operand:TI 0 "register_operand")
@@ -2019,7 +2088,15 @@
 		 (any_extend:TI (match_operand:DI 2 "register_operand"))))]
   "TARGET_64BIT && !(<CODE> == ZERO_EXTEND && TARGET_FIX_VR4120)"
 {
-  if (TARGET_FIX_R4000)
+  rtx hilo;
+
+  if (TARGET_MIPS16)
+    {
+      hilo = gen_rtx_REG (TImode, MD_REG_FIRST);
+      emit_insn (gen_<u>mulditi3_internal (hilo, operands[1], operands[2]));
+      emit_move_insn (operands[0], hilo);
+    }
+  else if (TARGET_FIX_R4000)
     emit_insn (gen_<u>mulditi3_r4000 (operands[0], operands[1], operands[2]));
   else
     emit_insn (gen_<u>mulditi3_internal (operands[0], operands[1],
@@ -2028,7 +2105,7 @@
 })
 
 (define_insn "<u>mulditi3_internal"
-  [(set (match_operand:TI 0 "register_operand" "=x")
+  [(set (match_operand:TI 0 "muldiv_target_operand" "=x")
 	(mult:TI (any_extend:TI (match_operand:DI 1 "register_operand" "d"))
 		 (any_extend:TI (match_operand:DI 2 "register_operand" "d"))))]
   "TARGET_64BIT
@@ -2067,11 +2144,11 @@
 ;; See the comment above <u>msubsidi4 for the relationship between
 ;; ISA_HAS_DSP and ISA_HAS_DSP_MULT.
 (define_insn "<u>maddsidi4"
-  [(set (match_operand:DI 0 "register_operand" "=ka")
+  [(set (match_operand:DI 0 "muldiv_target_operand" "=ka")
 	(plus:DI
 	 (mult:DI (any_extend:DI (match_operand:SI 1 "register_operand" "d"))
 		  (any_extend:DI (match_operand:SI 2 "register_operand" "d")))
-	 (match_operand:DI 3 "register_operand" "0")))]
+	 (match_operand:DI 3 "muldiv_target_operand" "0")))]
   "(TARGET_MAD || ISA_HAS_MACC || GENERATE_MADD_MSUB || ISA_HAS_DSP)
    && !TARGET_64BIT"
 {
@@ -2311,72 +2388,113 @@
 
 ;; VR4120 errata MD(A1): signed division instructions do not work correctly
 ;; with negative operands.  We use special libgcc functions instead.
-(define_insn_and_split "divmod<mode>4"
-  [(set (match_operand:GPR 0 "register_operand" "=l")
+(define_expand "divmod<mode>4"
+  [(set (match_operand:GPR 0 "register_operand")
+	(div:GPR (match_operand:GPR 1 "register_operand")
+		 (match_operand:GPR 2 "register_operand")))
+   (set (match_operand:GPR 3 "register_operand")
+	(mod:GPR (match_dup 1)
+		 (match_dup 2)))]
+  "!TARGET_FIX_VR4120"
+{
+  if (TARGET_MIPS16)
+    {
+      emit_insn (gen_divmod<mode>4_split (operands[3], operands[1],
+					  operands[2]));
+      emit_move_insn (operands[0], gen_rtx_REG (<MODE>mode, LO_REGNUM));
+    }
+  else
+    emit_insn (gen_divmod<mode>4_internal (operands[0], operands[1],
+					   operands[2], operands[3]));
+  DONE;
+})
+
+(define_insn_and_split "divmod<mode>4_internal"
+  [(set (match_operand:GPR 0 "muldiv_target_operand" "=l")
 	(div:GPR (match_operand:GPR 1 "register_operand" "d")
 		 (match_operand:GPR 2 "register_operand" "d")))
    (set (match_operand:GPR 3 "register_operand" "=d")
 	(mod:GPR (match_dup 1)
 		 (match_dup 2)))]
-  "!TARGET_FIX_VR4120"
+  "!TARGET_FIX_VR4120 && !TARGET_MIPS16"
   "#"
   "&& reload_completed"
   [(const_int 0)]
 {
-  rtx hilo;
-
-  if (TARGET_64BIT)
-    {
-      hilo = gen_rtx_REG (TImode, MD_REG_FIRST);
-      emit_insn (gen_divmod<mode>4_hilo_ti (hilo, operands[1], operands[2]));
-      emit_insn (gen_mfhi<mode>_ti (operands[3], hilo));
-    }
-  else
-    {
-      hilo = gen_rtx_REG (DImode, MD_REG_FIRST);
-      emit_insn (gen_divmod<mode>4_hilo_di (hilo, operands[1], operands[2]));
-      emit_insn (gen_mfhi<mode>_di (operands[3], hilo));
-    }
+  emit_insn (gen_divmod<mode>4_split (operands[3], operands[1], operands[2]));
   DONE;
 }
  [(set_attr "type" "idiv")
   (set_attr "mode" "<MODE>")
   (set_attr "length" "8")])
 
-(define_insn_and_split "udivmod<mode>4"
-  [(set (match_operand:GPR 0 "register_operand" "=l")
+(define_expand "udivmod<mode>4"
+  [(set (match_operand:GPR 0 "register_operand")
+	(udiv:GPR (match_operand:GPR 1 "register_operand")
+		  (match_operand:GPR 2 "register_operand")))
+   (set (match_operand:GPR 3 "register_operand")
+	(umod:GPR (match_dup 1)
+		  (match_dup 2)))]
+  ""
+{
+  if (TARGET_MIPS16)
+    {
+      emit_insn (gen_udivmod<mode>4_split (operands[3], operands[1],
+					   operands[2]));
+      emit_move_insn (operands[0], gen_rtx_REG (<MODE>mode, LO_REGNUM));
+    }
+  else
+    emit_insn (gen_udivmod<mode>4_internal (operands[0], operands[1],
+					    operands[2], operands[3]));
+  DONE;
+})
+
+(define_insn_and_split "udivmod<mode>4_internal"
+  [(set (match_operand:GPR 0 "muldiv_target_operand" "=l")
 	(udiv:GPR (match_operand:GPR 1 "register_operand" "d")
 		  (match_operand:GPR 2 "register_operand" "d")))
    (set (match_operand:GPR 3 "register_operand" "=d")
 	(umod:GPR (match_dup 1)
 		  (match_dup 2)))]
-  ""
+  "!TARGET_MIPS16"
   "#"
   "reload_completed"
   [(const_int 0)]
+{
+  emit_insn (gen_udivmod<mode>4_split (operands[3], operands[1], operands[2]));
+  DONE;
+}
+ [(set_attr "type" "idiv")
+  (set_attr "mode" "<MODE>")
+  (set_attr "length" "8")])
+
+(define_expand "<u>divmod<mode>4_split"
+  [(set (match_operand:GPR 0 "register_operand")
+	(any_mod:GPR (match_operand:GPR 1 "register_operand")
+		     (match_operand:GPR 2 "register_operand")))]
+  ""
 {
   rtx hilo;
 
   if (TARGET_64BIT)
     {
       hilo = gen_rtx_REG (TImode, MD_REG_FIRST);
-      emit_insn (gen_udivmod<mode>4_hilo_ti (hilo, operands[1], operands[2]));
-      emit_insn (gen_mfhi<mode>_ti (operands[3], hilo));
+      emit_insn (gen_<u>divmod<mode>4_hilo_ti (hilo, operands[1],
+					       operands[2]));
+      emit_insn (gen_mfhi<mode>_ti (operands[0], hilo));
     }
   else
     {
       hilo = gen_rtx_REG (DImode, MD_REG_FIRST);
-      emit_insn (gen_udivmod<mode>4_hilo_di (hilo, operands[1], operands[2]));
-      emit_insn (gen_mfhi<mode>_di (operands[3], hilo));
+      emit_insn (gen_<u>divmod<mode>4_hilo_di (hilo, operands[1],
+					       operands[2]));
+      emit_insn (gen_mfhi<mode>_di (operands[0], hilo));
     }
   DONE;
-}
- [(set_attr "type" "idiv")
-  (set_attr "mode" "<MODE>")
-  (set_attr "length" "8")])
+})
 
 (define_insn "<u>divmod<GPR:mode>4_hilo_<HILO:mode>"
-  [(set (match_operand:HILO 0 "register_operand" "=x")
+  [(set (match_operand:HILO 0 "muldiv_target_operand" "=x")
 	(unspec:HILO
 	  [(any_div:GPR (match_operand:GPR 1 "register_operand" "d")
 			(match_operand:GPR 2 "register_operand" "d"))]
@@ -4590,7 +4708,7 @@
 ;; and the errata related to -mfix-vr4130.
 (define_insn "mfhi<GPR:mode>_<HILO:mode>"
   [(set (match_operand:GPR 0 "register_operand" "=d")
-	(unspec:GPR [(match_operand:HILO 1 "register_operand" "x")]
+	(unspec:GPR [(match_operand:HILO 1 "hilo_operand" "x")]
 		    UNSPEC_MFHI))]
   ""
   { return ISA_HAS_MACCHI ? "<GPR:d>macchi\t%0,%.,%." : "mfhi\t%0"; }
diff --git a/gcc/config/mips/predicates.md b/gcc/config/mips/predicates.md
index dd5148067cd10e32ac9c4e4cc60130ba189c54c9..5e9398e69f3c171dd57e1d5d227a5317dc15e8ff 100644
--- a/gcc/config/mips/predicates.md
+++ b/gcc/config/mips/predicates.md
@@ -127,6 +127,11 @@
   (and (match_code "reg,subreg")
        (match_test "ST_REG_P (true_regnum (op))")))
 
+(define_predicate "muldiv_target_operand"
+  (if_then_else (match_test "TARGET_MIPS16")
+		(match_operand 0 "hilo_operand")
+		(match_operand 0 "register_operand")))
+
 (define_special_predicate "pc_or_label_operand"
   (match_code "pc,label_ref"))
 
@@ -189,7 +194,9 @@
 })
 
 (define_predicate "move_operand"
-  (match_operand 0 "general_operand")
+  ;; Allow HI and LO to be used as the source of a MIPS16 move.
+  (ior (match_operand 0 "general_operand")
+       (match_operand 0 "hilo_operand"))
 {
   enum mips_symbol_type symbol_type;
 
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index bfb1ac68a594f253153a14cff5f8115d6cacaf6e..c1bce164c7679ce7f84af6fe9d3c2e586f62d370 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,33 @@
+2011-11-27  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	* gcc.target/mips/mult-2.c, gcc.target/mips/mult-3.c,
+	gcc.target/mips/mult-4.c, gcc.target/mips/mult-5.c,
+	gcc.target/mips/mult-6.c, gcc.target/mips/mult-7.c,
+	gcc.target/mips/mult-8.c, gcc.target/mips/mult-9.c,
+	gcc.target/mips/mult-10.c, gcc.target/mips/mult-11.c,
+	gcc.target/mips/mult-12.c, gcc.target/mips/mult-13.c,
+	gcc.target/mips/mult-14.c, gcc.target/mips/mult-15.c,
+	gcc.target/mips/mult-16.c, gcc.target/mips/mult-17.c,
+	gcc.target/mips/mult-18.c, gcc.target/mips/mult-19.c,
+	gcc.target/mips/div-1.c, gcc.target/mips/div-2.c,
+	gcc.target/mips/div-3.c, gcc.target/mips/div-4.c,
+	gcc.target/mips/div-5.c, gcc.target/mips/div-6.c,
+	gcc.target/mips/div-7.c, gcc.target/mips/div-8.c,
+	gcc.target/mips/div-9.c, gcc.target/mips/div-10.c,
+	gcc.target/mips/div-11.c, gcc.target/mips/div-12.c: New tests.
+	* gcc.target/mips/fix-r4000-1.c (foo, bar): Add NOMIPS16.
+	* gcc.target/mips/fix-r4000-2.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-3.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-4.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-5.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-6.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-7.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-8.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-9.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-10.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-11.c (foo): Likewise.
+	* gcc.target/mips/fix-r4000-12.c (foo): Likewise.
+
 2011-11-27  Richard Sandiford  <rdsandiford@googlemail.com>
 
 	* gcc.target/mips/mips.exp (mips-dg-options): Make -mno-dsp
diff --git a/gcc/testsuite/gcc.target/mips/div-1.c b/gcc/testsuite/gcc.target/mips/div-1.c
new file mode 100644
index 0000000000000000000000000000000000000000..e1976c25e0dae136f92de86da9e72c321e252246
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-1.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tddiv\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return x / y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-10.c b/gcc/testsuite/gcc.target/mips/div-10.c
new file mode 100644
index 0000000000000000000000000000000000000000..23075da2c3deb0e1610b284aa47624a64abacc9e
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-10.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdivu\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x / y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-11.c b/gcc/testsuite/gcc.target/mips/div-11.c
new file mode 100644
index 0000000000000000000000000000000000000000..68f1658484b40e955b87f3dc2db1e82f3466a707
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-11.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdiv\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x % y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-12.c b/gcc/testsuite/gcc.target/mips/div-12.c
new file mode 100644
index 0000000000000000000000000000000000000000..c2384b20a9d1894c2098117819f0b06ab9acbb98
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-12.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdivu\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x % y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-2.c b/gcc/testsuite/gcc.target/mips/div-2.c
new file mode 100644
index 0000000000000000000000000000000000000000..af6e2fa8e1aab24ae96cc14c38c3fa48b3dddc08
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-2.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tddivu\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return x / y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-3.c b/gcc/testsuite/gcc.target/mips/div-3.c
new file mode 100644
index 0000000000000000000000000000000000000000..684b6a8e441cb0fa8a045fa9eb3cd606d19baa3a
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-3.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tddiv\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return x % y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-4.c b/gcc/testsuite/gcc.target/mips/div-4.c
new file mode 100644
index 0000000000000000000000000000000000000000..251b88f8164cc23a8ee376f1e4d6ed13e17f40fb
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-4.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tddivu\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return x % y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-5.c b/gcc/testsuite/gcc.target/mips/div-5.c
new file mode 100644
index 0000000000000000000000000000000000000000..a08f3e6f4bd80ac2b91b633147b7a74b84fb260e
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-5.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdiv\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x / y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-6.c b/gcc/testsuite/gcc.target/mips/div-6.c
new file mode 100644
index 0000000000000000000000000000000000000000..23075da2c3deb0e1610b284aa47624a64abacc9e
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-6.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdivu\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x / y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-7.c b/gcc/testsuite/gcc.target/mips/div-7.c
new file mode 100644
index 0000000000000000000000000000000000000000..68f1658484b40e955b87f3dc2db1e82f3466a707
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-7.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdiv\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x % y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-8.c b/gcc/testsuite/gcc.target/mips/div-8.c
new file mode 100644
index 0000000000000000000000000000000000000000..c2384b20a9d1894c2098117819f0b06ab9acbb98
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-8.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdivu\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x % y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/div-9.c b/gcc/testsuite/gcc.target/mips/div-9.c
new file mode 100644
index 0000000000000000000000000000000000000000..a08f3e6f4bd80ac2b91b633147b7a74b84fb260e
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/div-9.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdiv\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x / y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-1.c b/gcc/testsuite/gcc.target/mips/fix-r4000-1.c
index 513fc6130a545911401a32974ac97367b8d28b67..551d3549d846fcc1d5c4c4a7f836421526e58b47 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-1.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-1.c
@@ -1,6 +1,6 @@
 /* { dg-options "-march=r4000 -mfix-r4000 -O2 -dp" } */
 typedef int int32_t;
 typedef int uint32_t;
-int32_t foo (int32_t x, int32_t y) { return x * y; }
-uint32_t bar (uint32_t x, uint32_t y) { return x * y; }
+NOMIPS16 int32_t foo (int32_t x, int32_t y) { return x * y; }
+NOMIPS16 uint32_t bar (uint32_t x, uint32_t y) { return x * y; }
 /* { dg-final { scan-assembler-times "[concat {\tmult\t\$[45],\$[45][^\n]+mulsi3_r4000[^\n]+\n\tmflo\t\$2\n}]" 2 } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-10.c b/gcc/testsuite/gcc.target/mips/fix-r4000-10.c
index ebf3ca3056214a32c564c2fcad00aa2e7df83afa..8c938b7d2194bf11f3ab1423d9fe534009d07897 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-10.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-10.c
@@ -4,5 +4,5 @@
 /* { dg-options "-mips3 -mfix-r4000 -mgp64 -O2 -fno-split-wide-types -dp -EL" } */
 typedef unsigned long long uint64_t;
 typedef unsigned int uint128_t __attribute__((mode(TI)));
-uint128_t foo (uint64_t x, uint64_t y) { return (uint128_t) x * y; }
+NOMIPS16 uint128_t foo (uint64_t x, uint64_t y) { return (uint128_t) x * y; }
 /* { dg-final { scan-assembler "[concat {\tdmultu\t\$[45],\$[45][^\n]+umulditi3_r4000[^\n]+\n\tmflo\t\$2\n\tmfhi\t\$3\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-11.c b/gcc/testsuite/gcc.target/mips/fix-r4000-11.c
index 93f78134e4e29260fd98a037668caf1050ebfc79..7cfad3d2f79bc0863bf35cd8081e2ae4cd3c75c2 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-11.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-11.c
@@ -1,4 +1,4 @@
 /* { dg-options "-march=r4000 -mfix-r4000 -mgp64 -O2 -dp" } */
 typedef long long int64_t;
-int64_t foo (int64_t x) { return x / 11993; }
+NOMIPS16 int64_t foo (int64_t x) { return x / 11993; }
 /* { dg-final { scan-assembler "[concat {\tdmult\t\$4,\$[0-9]+[^\n]+smuldi3_highpart[^\n]+\n\tmfhi\t\$[0-9]+\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-12.c b/gcc/testsuite/gcc.target/mips/fix-r4000-12.c
index 554975ccca18c1eb6df30bdfa0c4d9693d48ef85..d449283ddf325a8e22aa36155cb8f3c654450bd6 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-12.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-12.c
@@ -1,4 +1,4 @@
 /* { dg-options "-march=r4000 -mfix-r4000 -mgp64 -O2 -dp" } */
 typedef unsigned long long uint64_t;
-uint64_t foo (uint64_t x) { return x / 11993; }
+NOMIPS16 uint64_t foo (uint64_t x) { return x / 11993; }
 /* { dg-final { scan-assembler "[concat {\tdmultu\t\$4,\$[0-9]+[^\n]+umuldi3_highpart[^\n]+\n\tmfhi\t\$[0-9]+\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-2.c b/gcc/testsuite/gcc.target/mips/fix-r4000-2.c
index 4f27041bedbbc1b7054d709b7b6a817b4a116edb..6cb7d3594e09ed7060a0fe7e3ff9fa1df326e7ff 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-2.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-2.c
@@ -1,7 +1,7 @@
 /* { dg-options "-mips1 -mfix-r4000 -O2 -dp -EB" } */
 typedef int int32_t;
 typedef long long int64_t;
-int32_t foo (int32_t x, int32_t y) { return ((int64_t) x * y) >> 32; }
+NOMIPS16 int32_t foo (int32_t x, int32_t y) { return ((int64_t) x * y) >> 32; }
 /* ??? A highpart pattern would be a better choice, but we currently
    don't use them.  */
 /* { dg-final { scan-assembler "[concat {\tmult\t\$[45],\$[45][^\n]+mulsidi3_32bit_r4000[^\n]+\n\tmflo\t\$3\n\tmfhi\t\$2\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-3.c b/gcc/testsuite/gcc.target/mips/fix-r4000-3.c
index 207fc66b062d20b26b48545bbed4f5d9708dcfda..bd12509d1bd9036af1668c16ca24fe0756def985 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-3.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-3.c
@@ -1,7 +1,7 @@
 /* { dg-options "-mips1 -mfix-r4000 -O2 -dp -EB" } */
 typedef unsigned int uint32_t;
 typedef unsigned long long uint64_t;
-uint32_t foo (uint32_t x, uint32_t y) { return ((uint64_t) x * y) >> 32; }
+NOMIPS16 uint32_t foo (uint32_t x, uint32_t y) { return ((uint64_t) x * y) >> 32; }
 /* ??? A highpart pattern would be a better choice, but we currently
    don't use them.  */
 /* { dg-final { scan-assembler "[concat {\tmultu\t\$[45],\$[45][^\n]+umulsidi3_32bit_r4000[^\n]+\n\tmflo\t\$3\n\tmfhi\t\$2\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-4.c b/gcc/testsuite/gcc.target/mips/fix-r4000-4.c
index be32b57ae4f5ef307a9cbe08889d82695c1e9246..3854db8967dc6df385baff279b76f0d9cdc97db0 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-4.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-4.c
@@ -4,5 +4,5 @@
 /* { dg-options "-mips1 -mfix-r4000 -O2 -fno-split-wide-types -dp -EL" } */
 typedef int int32_t;
 typedef long long int64_t;
-int64_t foo (int32_t x, int32_t y) { return (int64_t) x * y; }
+NOMIPS16 int64_t foo (int32_t x, int32_t y) { return (int64_t) x * y; }
 /* { dg-final { scan-assembler "[concat {\tmult\t\$[45],\$[45][^\n]+mulsidi3_32bit_r4000[^\n]+\n\tmflo\t\$2\n\tmfhi\t\$3\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-5.c b/gcc/testsuite/gcc.target/mips/fix-r4000-5.c
index c14e949f229dbc61ed7a26cc766258f8626988fc..c46300f62dbb6f31308addb4b155485c78765c05 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-5.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-5.c
@@ -4,5 +4,5 @@
 /* { dg-options "-mips1 -mfix-r4000 -O2 -fno-split-wide-types -dp -EL" } */
 typedef unsigned int uint32_t;
 typedef unsigned long long uint64_t;
-uint64_t foo (uint32_t x, uint32_t y) { return (uint64_t) x * y; }
+NOMIPS16 uint64_t foo (uint32_t x, uint32_t y) { return (uint64_t) x * y; }
 /* { dg-final { scan-assembler "[concat {\tmultu\t\$[45],\$[45][^\n]+umulsidi3_32bit_r4000[^\n]+\n\tmflo\t\$2\n\tmfhi\t\$3\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-6.c b/gcc/testsuite/gcc.target/mips/fix-r4000-6.c
index 32861f9750bc5343f6de08c2db80a353132391b6..1e33cc4f7656bccee4f7e419fef61f48761398a7 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-6.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-6.c
@@ -1,6 +1,6 @@
 /* { dg-options "-march=r4000 -mfix-r4000 -mgp64 -O2 -dp" } */
 typedef long long int64_t;
 typedef unsigned long long uint64_t;
-int64_t foo (int64_t x, int64_t y) { return x * y; }
-uint64_t bar (uint64_t x, uint64_t y) { return x * y; }
+NOMIPS16 int64_t foo (int64_t x, int64_t y) { return x * y; }
+NOMIPS16 uint64_t bar (uint64_t x, uint64_t y) { return x * y; }
 /* { dg-final { scan-assembler-times "[concat {\tdmult\t\$[45],\$[45][^\n]+muldi3_r4000[^\n]+\n\tmflo\t\$2\n}]" 2 } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-7.c b/gcc/testsuite/gcc.target/mips/fix-r4000-7.c
index 2555d5306d7f2810d1ce2aebc448f7007c9da801..118ba99dfebe2096ef9a8e659a96245d21b9f335 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-7.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-7.c
@@ -1,7 +1,7 @@
 /* { dg-options "-march=r4000 -mfix-r4000 -O2 -mgp64 -dp -EB" } */
 typedef long long int64_t;
 typedef int int128_t __attribute__((mode(TI)));
-int64_t foo (int64_t x, int64_t y) { return ((int128_t) x * y) >> 64; }
+NOMIPS16 int64_t foo (int64_t x, int64_t y) { return ((int128_t) x * y) >> 64; }
 /* ??? A highpart pattern would be a better choice, but we currently
    don't use them.  */
 /* { dg-final { scan-assembler "[concat {\tdmult\t\$[45],\$[45][^\n]+mulditi3[^\n]+\n\tmflo\t\$3\n\tmfhi\t\$2\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-8.c b/gcc/testsuite/gcc.target/mips/fix-r4000-8.c
index 964dc222291154f5a311a882ba6c2d47e37f2a2b..f2c71c1ef1a32d43f5d60877b24dafa9d0c92147 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-8.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-8.c
@@ -1,7 +1,7 @@
 /* { dg-options "-march=r4000 -mfix-r4000 -O2 -mgp64 -dp -EB" } */
 typedef unsigned long long uint64_t;
 typedef unsigned int uint128_t __attribute__((mode(TI)));
-uint64_t foo (uint64_t x, uint64_t y) { return ((uint128_t) x * y) >> 64; }
+NOMIPS16 uint64_t foo (uint64_t x, uint64_t y) { return ((uint128_t) x * y) >> 64; }
 /* ??? A highpart pattern would be a better choice, but we currently
    don't use them.  */
 /* { dg-final { scan-assembler "[concat {\tdmultu\t\$[45],\$[45][^\n]+umulditi3[^\n]+\n\tmflo\t\$3\n\tmfhi\t\$2\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/fix-r4000-9.c b/gcc/testsuite/gcc.target/mips/fix-r4000-9.c
index 68724eb376f7c63f2a4cde716659a22975aa525c..da9c11364d2e28411b53ed375933c6219a9b4965 100644
--- a/gcc/testsuite/gcc.target/mips/fix-r4000-9.c
+++ b/gcc/testsuite/gcc.target/mips/fix-r4000-9.c
@@ -4,5 +4,5 @@
 /* { dg-options "-mips3 -mfix-r4000 -mgp64 -O2 -fno-split-wide-types -dp -EL" } */
 typedef long long int64_t;
 typedef int int128_t __attribute__((mode(TI)));
-int128_t foo (int64_t x, int64_t y) { return (int128_t) x * y; }
+NOMIPS16 int128_t foo (int64_t x, int64_t y) { return (int128_t) x * y; }
 /* { dg-final { scan-assembler "[concat {\tdmult\t\$[45],\$[45][^\n]+mulditi3_r4000[^\n]+\n\tmflo\t\$2\n\tmfhi\t\$3\n}]" } } */
diff --git a/gcc/testsuite/gcc.target/mips/mult-10.c b/gcc/testsuite/gcc.target/mips/mult-10.c
new file mode 100644
index 0000000000000000000000000000000000000000..0b990c364135d51edb5c8eaebe66a5301bfd0e64
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-10.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O2 -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmult\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" { xfail *-*-* } } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return ((DI) x * y) >> 32;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-11.c b/gcc/testsuite/gcc.target/mips/mult-11.c
new file mode 100644
index 0000000000000000000000000000000000000000..d2ba695f6dda4ad683c344357b30ee96d0ad243e
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-11.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O2 -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return ((DI) x * y) >> 32;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-12.c b/gcc/testsuite/gcc.target/mips/mult-12.c
new file mode 100644
index 0000000000000000000000000000000000000000..bd772d2cd7420208ea39eda0d82d867d9d89451f
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-12.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu?\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-13.c b/gcc/testsuite/gcc.target/mips/mult-13.c
new file mode 100644
index 0000000000000000000000000000000000000000..e0859f629f3e342c5d7254140d137f8b9a46d060
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-13.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu?\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-14.c b/gcc/testsuite/gcc.target/mips/mult-14.c
new file mode 100644
index 0000000000000000000000000000000000000000..c4b54b7ec455b62fdedc4627b1de6bd29af5d5ce
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-14.c
@@ -0,0 +1,15 @@
+/* { dg-options "-O -mgp32 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmult\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler-not "\tdsll\t" } } */
+/* { dg-final { scan-assembler-not "\tdsrl\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 DI
+f (SI x, SI y)
+{
+  return (DI) x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-15.c b/gcc/testsuite/gcc.target/mips/mult-15.c
new file mode 100644
index 0000000000000000000000000000000000000000..a96049e04e6cdbdc2f27bf750368e3bd29def642
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-15.c
@@ -0,0 +1,15 @@
+/* { dg-options "-O -mgp32 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler-not "\tdsll\t" } } */
+/* { dg-final { scan-assembler-not "\tdsrl\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 DI
+f (SI x, SI y)
+{
+  return (DI) x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-16.c b/gcc/testsuite/gcc.target/mips/mult-16.c
new file mode 100644
index 0000000000000000000000000000000000000000..cb1707d912527d5c38b7fa80b14b43f10a2e97d1
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-16.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O2 -mgp32 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmult\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return ((DI) x * y) >> 32;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-17.c b/gcc/testsuite/gcc.target/mips/mult-17.c
new file mode 100644
index 0000000000000000000000000000000000000000..3539f63d96a946fa516206d0f7c4f398971da35f
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-17.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O -mgp32 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return ((DI) x * y) >> 32;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-18.c b/gcc/testsuite/gcc.target/mips/mult-18.c
new file mode 100644
index 0000000000000000000000000000000000000000..cfdac8b0de168c87efba337c6199898c58313014
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-18.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp32 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu?\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-19.c b/gcc/testsuite/gcc.target/mips/mult-19.c
new file mode 100644
index 0000000000000000000000000000000000000000..47cdd5c23c329e1dd3104be356b52daaa42b63ad
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-19.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp32 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu?\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 SI
+f (SI x, SI y)
+{
+  return x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-2.c b/gcc/testsuite/gcc.target/mips/mult-2.c
new file mode 100644
index 0000000000000000000000000000000000000000..8494e14c358ff6a9cd03c4749cb9a60e7a1f1168
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-2.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdmult\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+
+typedef int TI __attribute__((mode(TI)));
+typedef int DI __attribute__((mode(DI)));
+
+MIPS16 TI
+f (DI x, DI y)
+{
+  return (TI) x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-3.c b/gcc/testsuite/gcc.target/mips/mult-3.c
new file mode 100644
index 0000000000000000000000000000000000000000..fa7cfa34e23882919cf040066b947fafff8784ab
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-3.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdmultu\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+
+typedef unsigned int TI __attribute__((mode(TI)));
+typedef unsigned int DI __attribute__((mode(DI)));
+
+MIPS16 TI
+f (DI x, DI y)
+{
+  return (TI) x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-4.c b/gcc/testsuite/gcc.target/mips/mult-4.c
new file mode 100644
index 0000000000000000000000000000000000000000..d579f0023d2fbcd0eadb254c98c94234c5dd8cc2
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-4.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O2 -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdmult\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+
+typedef int TI __attribute__((mode(TI)));
+typedef int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return ((TI) x * y) >> 64;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-5.c b/gcc/testsuite/gcc.target/mips/mult-5.c
new file mode 100644
index 0000000000000000000000000000000000000000..6df86a1163dd2371b218880062d5d86cfd73e754
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-5.c
@@ -0,0 +1,13 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdmultu\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler-not "\tmflo\t" } } */
+
+typedef unsigned int TI __attribute__((mode(TI)));
+typedef unsigned int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return ((TI) x * y) >> 64;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-6.c b/gcc/testsuite/gcc.target/mips/mult-6.c
new file mode 100644
index 0000000000000000000000000000000000000000..a6b910ec4020c53d46d9b17bb959bd38bc2faf2c
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-6.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdmultu?\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-7.c b/gcc/testsuite/gcc.target/mips/mult-7.c
new file mode 100644
index 0000000000000000000000000000000000000000..7c2989baa52198093cc89fb49324cade0e6d476f
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-7.c
@@ -0,0 +1,12 @@
+/* { dg-options "-O -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tdmultu?\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler-not "\tmfhi\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+
+MIPS16 DI
+f (DI x, DI y)
+{
+  return x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-8.c b/gcc/testsuite/gcc.target/mips/mult-8.c
new file mode 100644
index 0000000000000000000000000000000000000000..3e3acde81e34fd5701eb28f3578dad030e4cea25
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-8.c
@@ -0,0 +1,15 @@
+/* { dg-options "-O2 -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmult\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler-times "\tdsll\t" 2 } } */
+/* { dg-final { scan-assembler "\tdsrl\t" } } */
+
+typedef int DI __attribute__((mode(DI)));
+typedef int SI __attribute__((mode(SI)));
+
+MIPS16 DI
+f (SI x, SI y)
+{
+  return (DI) x * y;
+}
diff --git a/gcc/testsuite/gcc.target/mips/mult-9.c b/gcc/testsuite/gcc.target/mips/mult-9.c
new file mode 100644
index 0000000000000000000000000000000000000000..aa2ededa67aa8904d430a197c4e9b71ae0b73e38
--- /dev/null
+++ b/gcc/testsuite/gcc.target/mips/mult-9.c
@@ -0,0 +1,15 @@
+/* { dg-options "-O2 -mgp64 (-mips16)" } */
+/* { dg-final { scan-assembler "\tmultu\t" } } */
+/* { dg-final { scan-assembler "\tmflo\t" } } */
+/* { dg-final { scan-assembler "\tmfhi\t" } } */
+/* { dg-final { scan-assembler-times "\tdsll\t" 2 } } */
+/* { dg-final { scan-assembler "\tdsrl\t" } } */
+
+typedef unsigned int DI __attribute__((mode(DI)));
+typedef unsigned int SI __attribute__((mode(SI)));
+
+MIPS16 DI
+f (SI x, SI y)
+{
+  return (DI) x * y;
+}