diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 80b48764948c223c16b8c67a407abfbf1b79d78c..8592db99d6fc34aee5b8c201c98772366d5b83d1 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,24 @@
+2009-07-23  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/24524
+	* trans-array.c (gfc_init_loopinfo): Initialize the reverse
+	field.
+	gfc_trans_scalarized_loop_end: If reverse set in dimension n,
+	reverse the scalarization loop.
+	gfc_conv_resolve_dependencies: Pass the reverse field of the
+	loopinfo to gfc_dep_resolver.
+	trans-expr.c (gfc_trans_assignment_1): Enable loop reversal for
+	assignment by resetting loop.reverse.
+	gfortran.h : Add the gfc_reverse enum.
+	trans.h : Add the reverse field to gfc_loopinfo.
+	dependency.c (gfc_check_dependency): Pass null to the new arg
+	of gfc_dep_resolver.
+	(gfc_check_section_vs_section): Check for reverse dependencies.
+	(gfc_dep_resolver): Add reverse argument and deal with the loop
+	reversal logic.
+	dependency.h : Modify prototype for gfc_dep_resolver to include
+	gfc_reverse *.
+
 2010-07-23  Daniel Kraft  <d@domob.eu>
 
 	PR fortran/44709
diff --git a/gcc/fortran/dependency.c b/gcc/fortran/dependency.c
index c21a2e43588be642f8487f9a75ca7e4e688f40e5..9dd4d9c46729917382e3ada8bcdfda876492b2fd 100644
--- a/gcc/fortran/dependency.c
+++ b/gcc/fortran/dependency.c
@@ -39,7 +39,8 @@ typedef enum
 {
   GFC_DEP_ERROR,
   GFC_DEP_EQUAL,	/* Identical Ranges.  */
-  GFC_DEP_FORWARD,	/* e.g., a(1:3), a(2:4).  */
+  GFC_DEP_FORWARD,	/* e.g., a(1:3) = a(2:4).  */
+  GFC_DEP_BACKWARD,	/* e.g. a(2:4) = a(1:3).  */
   GFC_DEP_OVERLAP,	/* May overlap in some other way.  */
   GFC_DEP_NODEP		/* Distinct ranges.  */
 }
@@ -831,7 +832,7 @@ gfc_check_dependency (gfc_expr *expr1, gfc_expr *expr2, bool identical)
       /* Identical and disjoint ranges return 0,
 	 overlapping ranges return 1.  */
       if (expr1->ref && expr2->ref)
-	return gfc_dep_resolver (expr1->ref, expr2->ref);
+	return gfc_dep_resolver (expr1->ref, expr2->ref, NULL);
 
       return 1;
 
@@ -1074,6 +1075,30 @@ gfc_check_section_vs_section (gfc_ref *lref, gfc_ref *rref, int n)
 	return GFC_DEP_FORWARD;
     }
 
+  /* Check for backward dependencies:
+     Are the strides the same?.  */
+  if ((!l_stride && !r_stride)
+	||
+      (l_stride && r_stride
+	&& gfc_dep_compare_expr (l_stride, r_stride) == 0))
+    {
+      /* x:y vs. x+1:z.  */
+      if (l_dir == 1 && r_dir == 1
+	    && l_start && r_start
+	    && gfc_dep_compare_expr (l_start, r_start) == 1
+	    && l_end && r_end
+	    && gfc_dep_compare_expr (l_end, r_end) == 1)
+	return GFC_DEP_BACKWARD;
+
+      /* x:y:-1 vs. x-1:z:-1.  */
+      if (l_dir == -1 && r_dir == -1
+	    && l_start && r_start
+	    && gfc_dep_compare_expr (l_start, r_start) == -1
+	    && l_end && r_end
+	    && gfc_dep_compare_expr (l_end, r_end) == -1)
+	return GFC_DEP_BACKWARD;
+    }
+
   return GFC_DEP_OVERLAP;
 }
 
@@ -1481,16 +1506,19 @@ ref_same_as_full_array (gfc_ref *full_ref, gfc_ref *ref)
 
 /* Finds if two array references are overlapping or not.
    Return value
+   	2 : array references are overlapping but reversal of one or
+	    more dimensions will clear the dependency.
    	1 : array references are overlapping.
    	0 : array references are identical or not overlapping.  */
 
 int
-gfc_dep_resolver (gfc_ref *lref, gfc_ref *rref)
+gfc_dep_resolver (gfc_ref *lref, gfc_ref *rref, gfc_reverse *reverse)
 {
   int n;
   gfc_dependency fin_dep;
   gfc_dependency this_dep;
 
+  this_dep = GFC_DEP_ERROR;
   fin_dep = GFC_DEP_ERROR;
   /* Dependencies due to pointers should already have been identified.
      We only need to check for overlapping array references.  */
@@ -1543,6 +1571,7 @@ gfc_dep_resolver (gfc_ref *lref, gfc_ref *rref)
 	      if (lref->u.ar.dimen_type[n] == DIMEN_VECTOR
 		  || rref->u.ar.dimen_type[n] == DIMEN_VECTOR)
 		return 1;
+
 	      if (lref->u.ar.dimen_type[n] == DIMEN_RANGE
 		  && rref->u.ar.dimen_type[n] == DIMEN_RANGE)
 		this_dep = gfc_check_section_vs_section (lref, rref, n);
@@ -1563,6 +1592,38 @@ gfc_dep_resolver (gfc_ref *lref, gfc_ref *rref)
 	      if (this_dep == GFC_DEP_NODEP)
 		return 0;
 
+	      /* Now deal with the loop reversal logic:  This only works on
+		 ranges and is activated by setting
+				reverse[n] == GFC_CAN_REVERSE
+		 The ability to reverse or not is set by previous conditions
+		 in this dimension.  If reversal is not activated, the
+		 value GFC_DEP_BACKWARD is reset to GFC_DEP_OVERLAP.  */
+	      if (rref->u.ar.dimen_type[n] == DIMEN_RANGE
+		    && lref->u.ar.dimen_type[n] == DIMEN_RANGE)
+		{
+		  /* Set reverse if backward dependence and not inhibited.  */
+		  if (reverse && reverse[n] != GFC_CANNOT_REVERSE)
+		    reverse[n] = (this_dep == GFC_DEP_BACKWARD) ?
+			         GFC_REVERSE_SET : reverse[n];
+
+		  /* Inhibit loop reversal if dependence not compatible.  */
+		  if (reverse && reverse[n] != GFC_REVERSE_NOT_SET
+		        && this_dep != GFC_DEP_EQUAL
+		        && this_dep != GFC_DEP_BACKWARD
+		        && this_dep != GFC_DEP_NODEP)
+		    {
+	              reverse[n] = GFC_CANNOT_REVERSE;
+		      if (this_dep != GFC_DEP_FORWARD)
+			this_dep = GFC_DEP_OVERLAP;
+		    }
+
+		  /* If no intention of reversing or reversing is explicitly
+		     inhibited, convert backward dependence to overlap.  */
+		  if ((reverse == NULL && this_dep == GFC_DEP_BACKWARD)
+			|| (reverse && reverse[n] == GFC_CANNOT_REVERSE))
+		    this_dep = GFC_DEP_OVERLAP;
+		}
+
 	      /* Overlap codes are in order of priority.  We only need to
 		 know the worst one.*/
 	      if (this_dep > fin_dep)
@@ -1578,7 +1639,7 @@ gfc_dep_resolver (gfc_ref *lref, gfc_ref *rref)
 
 	  /* Exactly matching and forward overlapping ranges don't cause a
 	     dependency.  */
-	  if (fin_dep < GFC_DEP_OVERLAP)
+	  if (fin_dep < GFC_DEP_BACKWARD)
 	    return 0;
 
 	  /* Keep checking.  We only have a dependency if
diff --git a/gcc/fortran/dependency.h b/gcc/fortran/dependency.h
index dd786bedabacb144717b5b5c84aa69b6e344d617..bac2749093b522a1e90c516eeb8cdd18f95e5f98 100644
--- a/gcc/fortran/dependency.h
+++ b/gcc/fortran/dependency.h
@@ -29,7 +29,6 @@ typedef enum
 }
 gfc_dep_check;
 
-
 /*********************** Functions prototypes **************************/
 
 bool gfc_ref_needs_temporary_p (gfc_ref *);
@@ -41,6 +40,6 @@ int gfc_check_dependency (gfc_expr *, gfc_expr *, bool);
 int gfc_is_same_range (gfc_array_ref *, gfc_array_ref *, int, int);
 int gfc_expr_is_one (gfc_expr *, int);
 
-int gfc_dep_resolver(gfc_ref *, gfc_ref *);
+int gfc_dep_resolver(gfc_ref *, gfc_ref *, gfc_reverse *);
 int gfc_are_equivalenced_arrays (gfc_expr *, gfc_expr *);
 
diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index 401e501c41ddcad7993a99246938206c7ffd1af8..a493866ab3691848adf49cb2d45a449a68f43ccb 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -576,6 +576,15 @@ typedef enum
 }
 gfc_fcoarray;
 
+typedef enum
+{
+  GFC_REVERSE_NOT_SET,
+  GFC_REVERSE_SET,
+  GFC_CAN_REVERSE,
+  GFC_CANNOT_REVERSE
+}
+gfc_reverse;
+
 /************************* Structures *****************************/
 
 /* Used for keeping things in balanced binary trees.  */
diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index d4f1cdf8f6783b84a3b411d1a6a0aca83106b61c..cca4ecc4d9c5c83e5e5687e269e4c67eb78c340e 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -2180,9 +2180,12 @@ gfc_init_loopinfo (gfc_loopinfo * loop)
   gfc_init_block (&loop->pre);
   gfc_init_block (&loop->post);
 
-  /* Initially scalarize in order.  */
+  /* Initially scalarize in order and default to no loop reversal.  */
   for (n = 0; n < GFC_MAX_DIMENSIONS; n++)
-    loop->order[n] = n;
+    {
+      loop->order[n] = n;
+      loop->reverse[n] = GFC_CANNOT_REVERSE;
+    }
 
   loop->ss = gfc_ss_terminator;
 }
@@ -2842,8 +2845,18 @@ gfc_trans_scalarized_loop_end (gfc_loopinfo * loop, int n,
     }
   else
     {
+      bool reverse_loop = (loop->reverse[n] == GFC_REVERSE_SET)
+			     && (loop->temp_ss == NULL);
+
       loopbody = gfc_finish_block (pbody);
 
+      if (reverse_loop)
+	{
+	  tmp = loop->from[n];
+	  loop->from[n] = loop->to[n];
+	  loop->to[n] = tmp;
+	}
+
       /* Initialize the loopvar.  */
       if (loop->loopvar[n] != loop->from[n])
 	gfc_add_modify (&loop->code[n], loop->loopvar[n], loop->from[n]);
@@ -2854,8 +2867,8 @@ gfc_trans_scalarized_loop_end (gfc_loopinfo * loop, int n,
       gfc_init_block (&block);
 
       /* The exit condition.  */
-      cond = fold_build2 (GT_EXPR, boolean_type_node,
-			 loop->loopvar[n], loop->to[n]);
+      cond = fold_build2 (reverse_loop ? LT_EXPR : GT_EXPR,
+			  boolean_type_node, loop->loopvar[n], loop->to[n]);
       tmp = build1_v (GOTO_EXPR, exit_label);
       TREE_USED (exit_label) = 1;
       tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
@@ -2865,8 +2878,10 @@ gfc_trans_scalarized_loop_end (gfc_loopinfo * loop, int n,
       gfc_add_expr_to_block (&block, loopbody);
 
       /* Increment the loopvar.  */
-      tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
-			 loop->loopvar[n], gfc_index_one_node);
+      tmp = fold_build2 (reverse_loop ? MINUS_EXPR : PLUS_EXPR,
+			 gfc_array_index_type, loop->loopvar[n],
+			 gfc_index_one_node);
+
       gfc_add_modify (&block, loop->loopvar[n], tmp);
 
       /* Build the loop.  */
@@ -3449,7 +3464,8 @@ gfc_conv_resolve_dependencies (gfc_loopinfo * loop, gfc_ss * dest,
 	  lref = dest->expr->ref;
 	  rref = ss->expr->ref;
 
-	  nDepend = gfc_dep_resolver (lref, rref);
+	  nDepend = gfc_dep_resolver (lref, rref, &loop->reverse[0]);
+
 	  if (nDepend == 1)
 	    break;
 #if 0
diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 09ad110ff48c1d2dd24b0103fa5c787a70716cc4..a83d4b3eda4d07c79d08af6bd86cbacc1f824d35 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -5303,6 +5303,7 @@ gfc_trans_assignment_1 (gfc_expr * expr1, gfc_expr * expr2, bool init_flag,
   bool l_is_temp;
   bool scalar_to_array;
   tree string_length;
+  int n;
 
   /* Assignment of the form lhs = rhs.  */
   gfc_start_block (&block);
@@ -5348,6 +5349,9 @@ gfc_trans_assignment_1 (gfc_expr * expr1, gfc_expr * expr2, bool init_flag,
 
       /* Calculate the bounds of the scalarization.  */
       gfc_conv_ss_startstride (&loop);
+      /* Enable loop reversal.  */
+      for (n = 0; n < loop.dimen; n++)
+	loop.reverse[n] = GFC_REVERSE_NOT_SET;
       /* Resolve any data dependencies in the statement.  */
       gfc_conv_resolve_dependencies (&loop, lss, rss);
       /* Setup the scalarizing loops.  */
diff --git a/gcc/fortran/trans.h b/gcc/fortran/trans.h
index cbed52b5f870121fcdb29394abd946654baa84d7..9872e83df9e75074050125011ad19a3ebd7b51e1 100644
--- a/gcc/fortran/trans.h
+++ b/gcc/fortran/trans.h
@@ -240,6 +240,9 @@ typedef struct gfc_loopinfo
   /* Order in which the dimensions should be looped, innermost first.  */
   int order[GFC_MAX_DIMENSIONS];
 
+  /* Enum to control loop reversal.  */
+  gfc_reverse reverse[GFC_MAX_DIMENSIONS];
+
   /* The number of dimensions for which a temporary is used.  */
   int temp_dim;