diff --git a/gcc/config/rs6000/genfusion.pl b/gcc/config/rs6000/genfusion.pl
index e4db352e0ce608eb53a5ad26ed5cd71e2960c809..2851bb73e852b5ba69e1ec06380f23b538d8d184 100755
--- a/gcc/config/rs6000/genfusion.pl
+++ b/gcc/config/rs6000/genfusion.pl
@@ -53,92 +53,113 @@ sub mode_to_ldst_char
     return '?';
 }
 
+sub gen_ld_cmpi_p10_one
+{
+  my ($lmode, $result, $ccmode) = @_;
+
+  my $np = "NON_PREFIXED_D";
+  my $mempred = "non_update_memory_operand";
+  my $extend;
+
+  if ($ccmode eq "CC") {
+    # ld and lwa are both DS-FORM.
+    ($lmode =~ /^[SD]I$/) and $np = "NON_PREFIXED_DS";
+    ($lmode =~ /^[SD]I$/) and $mempred = "ds_form_mem_operand";
+  } else {
+    if ($lmode eq "DI") {
+      # ld is DS-form, but lwz is not.
+      $np = "NON_PREFIXED_DS";
+      $mempred = "ds_form_mem_operand";
+    }
+  }
+
+  my $cmpl = ($ccmode eq "CC") ? "" : "l";
+  my $echr = ($ccmode eq "CC") ? "a" : "z";
+  if ($lmode eq "DI") { $echr = ""; }
+  my $constpred = ($ccmode eq "CC") ? "const_m1_to_1_operand"
+  				    : "const_0_to_1_operand";
+
+  # For clobber, we need a SI/DI reg in case we
+  # split because we have to sign/zero extend.
+  my $clobbermode = ($lmode =~ /^[QH]I$/) ? "GPR" : $lmode;
+  if ($result =~ /^EXT/ || $result eq "GPR" || $clobbermode eq "GPR") {
+    # We always need extension if result > lmode.
+    $extend = ($ccmode eq "CC") ? "sign" : "zero";
+  } else {
+    # Result of SI/DI does not need sign extension.
+    $extend = "none";
+  }
+
+  my $ldst = mode_to_ldst_char($lmode);
+  print <<HERE;
+;; load-cmpi fusion pattern generated by gen_ld_cmpi_p10
+;; load mode is $lmode result mode is $result compare mode is $ccmode extend is $extend
+(define_insn_and_split "*l${ldst}${echr}_cmp${cmpl}di_cr0_${lmode}_${result}_${ccmode}_${extend}"
+  [(set (match_operand:${ccmode} 2 "cc_reg_operand" "=x")
+        (compare:${ccmode} (match_operand:${lmode} 1 "${mempred}" "m")
+HERE
+  print "   " if $ccmode eq "CCUNS";
+print <<HERE;
+                    (match_operand:${lmode} 3 "${constpred}" "n")))
+HERE
+
+  if ($result eq "clobber") {
+    print <<HERE;
+   (clobber (match_scratch:${clobbermode} 0 "=r"))]
+HERE
+  } elsif ($result eq $lmode) {
+    print <<HERE;
+   (set (match_operand:${result} 0 "gpc_reg_operand" "=r") (match_dup 1))]
+HERE
+  } else {
+    print <<HERE;
+   (set (match_operand:${result} 0 "gpc_reg_operand" "=r") (${extend}_extend:${result} (match_dup 1)))]
+HERE
+  }
+
+  print <<HERE;
+  "(TARGET_P10_FUSION)"
+  "l${ldst}${echr}%X1 %0,%1\\;cmp${cmpl}di %2,%0,%3"
+  "&& reload_completed
+   && (cc_reg_not_cr0_operand (operands[2], CCmode)
+       || !address_is_non_pfx_d_or_x (XEXP (operands[1], 0),
+                                      ${lmode}mode, ${np}))"
+HERE
+
+  if ($extend eq "none") {
+    print "  [(set (match_dup 0) (match_dup 1))\n";
+  } elsif ($result eq "clobber") {
+    print "  [(set (match_dup 0) (${extend}_extend:${clobbermode} (match_dup 1)))\n";
+  } else {
+    print "  [(set (match_dup 0) (${extend}_extend:${result} (match_dup 1)))\n";
+  }
+
+  print <<HERE;
+   (set (match_dup 2)
+        (compare:${ccmode} (match_dup 0) (match_dup 3)))]
+  ""
+  [(set_attr "type" "fused_load_cmpi")
+   (set_attr "cost" "8")
+   (set_attr "length" "8")])
+
+HERE
+}
+
 sub gen_ld_cmpi_p10
 {
-    my ($lmode, $ldst, $clobbermode, $result, $cmpl, $echr, $constpred,
-	$mempred, $ccmode, $np, $extend, $resultmode);
-  LMODE: foreach $lmode ('DI','SI','HI','QI') {
-      $ldst = mode_to_ldst_char($lmode);
-      $clobbermode = $lmode;
-      # For clobber, we need a SI/DI reg in case we
-      # split because we have to sign/zero extend.
-      if ($lmode eq 'HI' || $lmode eq 'QI') { $clobbermode = "GPR"; }
-    RESULT: foreach $result ('clobber', $lmode,  "EXT".$lmode) {
-	# EXTDI does not exist, and we cannot directly produce HI/QI results.
-	next RESULT if $result eq "EXTDI" || $result eq "HI" || $result eq "QI";
-	# Don't allow EXTQI because that would allow HI result which we can't do.
-	$result = "GPR" if $result eq "EXTQI";
-      CCMODE: foreach $ccmode ('CC','CCUNS') {
-	  $np = "NON_PREFIXED_D";
-	  $mempred = "non_update_memory_operand";
-	  if ( $ccmode eq 'CC' ) {
-	      next CCMODE if $lmode eq 'QI';
-	      if ( $lmode eq 'DI' || $lmode eq 'SI' ) {
-		  # ld and lwa are both DS-FORM.
-		  $np = "NON_PREFIXED_DS";
-		  $mempred = "ds_form_mem_operand";
-	      }
-	      $cmpl = "";
-	      $echr = "a";
-	      $constpred = "const_m1_to_1_operand";
-	  } else {
-	      if ( $lmode eq 'DI' ) {
-		  # ld is DS-form, but lwz is not.
-		  $np = "NON_PREFIXED_DS";
-		  $mempred = "ds_form_mem_operand";
-	      }
-	      $cmpl = "l";
-	      $echr = "z";
-	      $constpred = "const_0_to_1_operand";
-	  }
-	  if ($lmode eq 'DI') { $echr = ""; }
-	  if ($result =~ m/^EXT/ || $result eq 'GPR' || $clobbermode eq 'GPR') {
-	      # We always need extension if result > lmode.
-	      if ( $ccmode eq 'CC' ) {
-		  $extend = "sign";
-	      } else {
-		  $extend = "zero";
-	      }
-	  } else {
-	      # Result of SI/DI does not need sign extension.
-	      $extend = "none";
-	  }
-	  print ";; load-cmpi fusion pattern generated by gen_ld_cmpi_p10\n";
-	  print ";; load mode is $lmode result mode is $result compare mode is $ccmode extend is $extend\n";
+  foreach my $lmode (qw/DI SI HI QI/) {
+    foreach my $result ("clobber", $lmode,  "EXT$lmode") {
+      # EXTDI does not exist, and we cannot directly produce HI/QI results.
+      next if $result =~ /^(QI|HI|EXTDI)$/;
 
-	  print "(define_insn_and_split \"*l${ldst}${echr}_cmp${cmpl}di_cr0_${lmode}_${result}_${ccmode}_${extend}\"\n";
-	  print "  [(set (match_operand:${ccmode} 2 \"cc_reg_operand\" \"=x\")\n";
-	  print "        (compare:${ccmode} (match_operand:${lmode} 1 \"${mempred}\" \"m\")\n";
-	  if ($ccmode eq 'CCUNS') { print "   "; }
-	  print "                    (match_operand:${lmode} 3 \"${constpred}\" \"n\")))\n";
-	  if ($result eq 'clobber') {
-	      print "   (clobber (match_scratch:${clobbermode} 0 \"=r\"))]\n";
-	  } elsif ($result eq $lmode) {
-	      print "   (set (match_operand:${result} 0 \"gpc_reg_operand\" \"=r\") (match_dup 1))]\n";
-	  } else {
-	      print "   (set (match_operand:${result} 0 \"gpc_reg_operand\" \"=r\") (${extend}_extend:${result} (match_dup 1)))]\n";
-	  }
-	  print "  \"(TARGET_P10_FUSION)\"\n";
-	  print "  \"l${ldst}${echr}%X1 %0,%1\\;cmp${cmpl}di %2,%0,%3\"\n";
-	  print "  \"&& reload_completed\n";
-	  print "   && (cc_reg_not_cr0_operand (operands[2], CCmode)\n";
-	  print "       || !address_is_non_pfx_d_or_x (XEXP (operands[1], 0),\n";
-	  print "                                      ${lmode}mode, ${np}))\"\n";
+      # Don't allow EXTQI because that would allow HI result which we can't do.
+      $result = "GPR" if $result eq "EXTQI";
 
-	  if ($extend eq "none") {
-	      print "  [(set (match_dup 0) (match_dup 1))\n";
-	  } else {
-	      $resultmode = $result;
-	      if ( $result eq 'clobber' ) { $resultmode = $clobbermode }
-	      print "  [(set (match_dup 0) (${extend}_extend:${resultmode} (match_dup 1)))\n";
-	  }
-	  print "   (set (match_dup 2)\n";
-	  print "        (compare:${ccmode} (match_dup 0) (match_dup 3)))]\n";
-	  print "  \"\"\n";
-	  print "  [(set_attr \"type\" \"fused_load_cmpi\")\n";
-	  print "   (set_attr \"cost\" \"8\")\n";
-	  print "   (set_attr \"length\" \"8\")])\n";
-	  print "\n";
+      foreach my $ccmode (qw/CC CCUNS/) {
+	# We do not have signed single-byte loads.
+	next if ($lmode eq "QI" and $ccmode eq "CC");
+
+	gen_ld_cmpi_p10_one($lmode, $result, $ccmode);
       }
     }
   }