int eff_dimen;
need_impl_this_image =
- ar->dimen_type[ar->dimen + ar->codimen - 1] == DIMEN_THIS_IMAGE;
+ ar->dimen_type[ar->dimen + ar->codimen - 1] == DIMEN_THIS_IMAGE;
if (flag_coarray == GFC_FCOARRAY_SHARED
&& !need_impl_this_image)
add_to_offset (&cst_offset, &offset, tmp);
}
- if (flag_coarray == GFC_FCOARRAY_SHARED && need_impl_this_image)
+ if (flag_coarray == GFC_FCOARRAY_SHARED && need_impl_this_image
+ && !se->no_impl_this_image)
{
tree off;
tree co_stride = gfc_conv_array_stride (decl, eff_dimen + 1);
--- /dev/null
+! { dg-do run }
+! { dg-set-target-env-var GFORTRAN_NUM_IMAGES "2" }
+!
+implicit none
+integer, allocatable :: A[:], B[:,:]
+integer :: n1, n2, n3
+
+if (allocated (a)) STOP 1
+if (allocated (b)) STOP 2
+
+allocate(a[*])
+a = 5 + this_image ()
+if (a[this_image ()] /= 5 + this_image ()) STOP 1
+
+a[this_image ()] = 8 - 2*this_image ()
+if (a[this_image ()] /= 8 - 2*this_image ()) STOP 2
+
+if (lcobound(a, dim=1) /= 1 .or. ucobound(a,dim=1) /= num_images()) &
+ STOP 3
+deallocate(a)
+
+allocate(a[4:*])
+a[this_image ()] = 8 - 2*this_image ()
+
+if (lcobound(a, dim=1) /= 4 .or. ucobound(a,dim=1) /= 3 + num_images()) &
+ STOP 4
+
+n1 = -1
+n2 = 5
+n3 = 3
+allocate (B[n1:n2, n3:*])
+if (any (lcobound(b) /= [-1, 3]) .or. lcobound(B, dim=2) /= n3) &
+ STOP 5
+call sub(A, B)
+
+if (allocated (a)) STOP 6
+if (.not.allocated (b)) STOP 7
+
+call two(.true.)
+call two(.false.)
+
+! automatically deallocate "B"
+contains
+ subroutine sub(x, y)
+ integer, allocatable :: x[:], y[:,:]
+
+ if (any (lcobound(y) /= [-1, 3]) .or. lcobound(y, dim=2) /= n3) &
+ STOP 8
+ if (lcobound(x, dim=1) /= 4 .or. ucobound(x,dim=1) /= 3 + num_images()) &
+ STOP 9
+ if (x[this_image ()] /= 8 - 2*this_image ()) STOP 3
+ deallocate(x)
+ end subroutine sub
+
+ subroutine two(init)
+ logical, intent(in) :: init
+ integer, allocatable, SAVE :: a[:]
+
+ if (init) then
+ if (allocated(a)) STOP 10
+ allocate(a[*])
+ a = 45
+ else
+ if (.not. allocated(a)) STOP 11
+ if (a /= 45) STOP 12
+ deallocate(a)
+ end if
+ end subroutine two
+end
--- /dev/null
+! { dg-do run }
+! { dg-set-target-env-var GFORTRAN_NUM_IMAGES "4" }
+! Check whether registering allocatable coarrays works
+!
+type position
+ real :: x, y, z
+end type position
+
+integer, allocatable :: a[:]
+type(position), allocatable :: p[:]
+
+allocate(a[*])
+a = 7
+
+allocate(p[*])
+p%x = 11
+p%y = 13
+p%z = 15
+
+if (a /= 7) STOP 1
+a = 88
+if (a /= 88) STOP 2
+
+if (p%x /= 11) STOP 3
+p%x = 17
+if (p%x /= 17) STOP 4
+
+ block
+ integer, allocatable :: b[:]
+
+ allocate(b[*])
+ b = 8494
+
+ if (b /= 8494) STOP 5
+ end block
+
+if (a /= 88) STOP 6
+call test ()
+end
+
+subroutine test()
+ type velocity
+ real :: x, y, z
+ end type velocity
+
+ real, allocatable :: z[:]
+ type(velocity), allocatable :: v[:]
+
+ allocate(z[*])
+ z = sqrt(2.0)
+
+ allocate(v[*])
+ v%x = 21
+ v%y = 23
+ v%z = 25
+
+ if (z /= sqrt(2.0)) STOP 7
+ if (v%x /= 21) STOP 8
+
+end subroutine test