re PR fortran/53526 ([Coarray] (lib) Properly handle MOVE_ALLOC for coarrays)
authorTobias Burnus <burnus@net-b.de>
Mon, 18 Jun 2012 18:15:51 +0000 (20:15 +0200)
committerTobias Burnus <burnus@gcc.gnu.org>
Mon, 18 Jun 2012 18:15:51 +0000 (20:15 +0200)
2012-06-18  Tobias Burnus  <burnus@net-b.de>

        PR fortran/53526
        * trans-intrinsic.c (conv_intrinsic_move_alloc): Handle
        * coarrays.

2012-06-18  Tobias Burnus  <burnus@net-b.de>

        PR fortran/53526
        * gfortran.dg/coarray_lib_move_alloc_1.f90: New.

From-SVN: r188748

gcc/fortran/ChangeLog
gcc/fortran/trans-intrinsic.c
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/coarray/move_alloc_1.f90 [new file with mode: 0644]
gcc/testsuite/gfortran.dg/coarray_lib_move_alloc_1.f90 [new file with mode: 0644]

index 6469d676d394d363523b569e023e52a6ab8e6135..8be714221b8a0ba013dd553bbeaf07e299924803 100644 (file)
@@ -1,3 +1,8 @@
+2012-06-18  Tobias Burnus  <burnus@net-b.de>
+
+       PR fortran/53526
+       * trans-intrinsic.c (conv_intrinsic_move_alloc): Handle coarrays.
+
 2012-06-18  Tobias Burnus  <burnus@net-b.de>
 
        PR fortran/53526
index 04d6caab183c72704957c077a67c924ed84bc7f6..8cce42744bf20e9552c49c9fd1d3f3cf8e005c98 100644 (file)
@@ -7243,6 +7243,7 @@ conv_intrinsic_move_alloc (gfc_code *code)
   gfc_se from_se, to_se;
   gfc_ss *from_ss, *to_ss;
   tree tmp;
+  bool coarray;
 
   gfc_start_block (&block);
 
@@ -7254,8 +7255,9 @@ conv_intrinsic_move_alloc (gfc_code *code)
 
   gcc_assert (from_expr->ts.type != BT_CLASS
              || to_expr->ts.type == BT_CLASS);
+  coarray = gfc_get_corank (from_expr) != 0;
 
-  if (from_expr->rank == 0)
+  if (from_expr->rank == 0 && !coarray)
     {
       if (from_expr->ts.type != BT_CLASS)
        from_expr2 = from_expr;
@@ -7366,15 +7368,50 @@ conv_intrinsic_move_alloc (gfc_code *code)
     }
 
   /* Deallocate "to".  */
-  to_ss = gfc_walk_expr (to_expr);
-  from_ss = gfc_walk_expr (from_expr);
+  if (from_expr->rank != 0)
+    {
+      to_ss = gfc_walk_expr (to_expr);
+      from_ss = gfc_walk_expr (from_expr);
+    }
+  else
+    {
+      to_ss = walk_coarray (to_expr);
+      from_ss = walk_coarray (from_expr);
+    }
   gfc_conv_expr_descriptor (&to_se, to_expr, to_ss);
   gfc_conv_expr_descriptor (&from_se, from_expr, from_ss);
 
-  tmp = gfc_conv_descriptor_data_get (to_se.expr);
-  tmp = gfc_deallocate_with_status (tmp, NULL_TREE, NULL_TREE, NULL_TREE,
-                                   NULL_TREE, true, to_expr, false);
-  gfc_add_expr_to_block (&block, tmp);
+  /* For coarrays, call SYNC ALL if TO is already deallocated as MOVE_ALLOC
+     is an image control "statement", cf. IR F08/0040 in 12-006A.  */
+  if (coarray && gfc_option.coarray == GFC_FCOARRAY_LIB)
+    {
+      tree cond;
+
+      tmp = gfc_deallocate_with_status (to_se.expr, NULL_TREE, NULL_TREE,
+                                       NULL_TREE, NULL_TREE, true, to_expr,
+                                       true);
+      gfc_add_expr_to_block (&block, tmp);
+
+      tmp = gfc_conv_descriptor_data_get (to_se.expr);
+      cond = fold_build2_loc (input_location, EQ_EXPR,
+                             boolean_type_node, tmp,
+                             fold_convert (TREE_TYPE (tmp),
+                                           null_pointer_node));
+      tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_sync_all,
+                                3, null_pointer_node, null_pointer_node,
+                                build_int_cst (integer_type_node, 0));
+
+      tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond,
+                            tmp, build_empty_stmt (input_location));
+      gfc_add_expr_to_block (&block, tmp);
+    }
+  else
+    {
+      tmp = gfc_conv_descriptor_data_get (to_se.expr);
+      tmp = gfc_deallocate_with_status (tmp, NULL_TREE, NULL_TREE, NULL_TREE,
+                                       NULL_TREE, true, to_expr, false);
+      gfc_add_expr_to_block (&block, tmp);
+    }
 
   /* Move the pointer and update the array descriptor data.  */
   gfc_add_modify_loc (input_location, &block, to_se.expr, from_se.expr);
index c1b129ab51b6495afd76d8b63e90afc87376989e..e8c27eca98d1103c71398c0ab3fed1975de554fc 100644 (file)
@@ -1,3 +1,9 @@
+2012-06-18  Tobias Burnus  <burnus@net-b.de>
+
+       PR fortran/53526
+       * gfortran.dg/coarray_lib_move_alloc_1.f90: New.
+       * gfortran.dg/coarray/move_alloc_1.f90
+
 2012-06-18  Tobias Burnus  <burnus@net-b.de>
 
        PR fortran/53526
diff --git a/gcc/testsuite/gfortran.dg/coarray/move_alloc_1.f90 b/gcc/testsuite/gfortran.dg/coarray/move_alloc_1.f90
new file mode 100644 (file)
index 0000000..1f32052
--- /dev/null
@@ -0,0 +1,24 @@
+! { dg-do run }
+!
+! PR fortran/53526
+!
+! Check handling of move_alloc with coarrays
+!
+implicit none
+integer, allocatable :: u[:], v[:], w(:)[:,:], x(:)[:,:]
+
+allocate (u[4:*])
+call move_alloc (u, v)
+if (allocated (u)) call abort ()
+if (lcobound (v, dim=1) /= 4) call abort ()
+if (ucobound (v, dim=1) /= 3 + num_images()) call abort ()
+
+allocate (w(-2:3)[4:5,-1:*])
+call move_alloc (w, x)
+if (allocated (w)) call abort ()
+if (lbound (x, dim=1) /= -2) call abort ()
+if (ubound (x, dim=1) /= 3) call abort ()
+if (any (lcobound (x) /= [4, -1])) call abort ()
+if (any (ucobound (x) /= [5, -2 + (num_images()+1)/2])) call abort ()
+
+end
diff --git a/gcc/testsuite/gfortran.dg/coarray_lib_move_alloc_1.f90 b/gcc/testsuite/gfortran.dg/coarray_lib_move_alloc_1.f90
new file mode 100644 (file)
index 0000000..fef9d71
--- /dev/null
@@ -0,0 +1,23 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib -fdump-tree-original" }
+!
+! PR fortran/53526
+!
+! Check handling of move_alloc with coarrays
+
+subroutine ma_scalar (aa, bb)
+  integer, allocatable :: aa[:], bb[:]
+  call move_alloc(aa,bb)
+end
+
+subroutine ma_array (cc, dd)
+  integer, allocatable :: cc(:)[:], dd(:)[:]
+  call move_alloc (cc, dd)
+end
+
+! { dg-final { scan-tree-dump-times "free" 0 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_sync_all" 2 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister" 2 "original" } }
+! { dg-final { scan-tree-dump-times "\\*bb = \\*aa" 1 "original" } }
+! { dg-final { scan-tree-dump-times "\\*dd = \\*cc" 1 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }