2 ! { dg-options "-fcoarray=single -fcheck=bounds" }
4 ! Coarray support -- allocatable array coarrays
5 ! -- intrinsic procedures
11 integer,allocatable
:: B(:)[:]
23 integer, allocatable
:: a(:)[:,:,:]
24 allocate(a(1)[-4:9,8,4:*])
26 if (this_image(a
,dim
=1) /= -4_8) call abort()
27 if (lcobound (a
,dim
=1) /= -4_8) call abort()
28 if (ucobound (a
,dim
=1) /= 9_8) call abort()
30 if (this_image(a
,dim
=2) /= 1_8) call abort()
31 if (lcobound (a
,dim
=2) /= 1_8) call abort()
32 if (ucobound (a
,dim
=2) /= 8_8) call abort()
34 if (this_image(a
,dim
=3) /= 4_8) call abort()
35 if (lcobound (a
,dim
=3) /= 4_8) call abort()
36 if (ucobound (a
,dim
=3) /= 4_8) call abort()
38 if (any(this_image(a
) /= [-4_8, 1_8, 4_8])) call abort()
39 if (any(lcobound (a
) /= [-4_8, 1_8, 4_8])) call abort()
40 if (any(ucobound (a
) /= [9_8, 8_8, 4_8])) call abort()
44 integer, allocatable
:: a(:)[:,:,:]
45 allocate(a(1)[-4:9,8,4:*])
47 if (this_image(a
,dim
=1) /= -4) call abort()
48 if (lcobound (a
,dim
=1) /= -4) call abort()
49 if (ucobound (a
,dim
=1) /= 9) call abort()
51 if (this_image(a
,dim
=2) /= 1) call abort()
52 if (lcobound (a
,dim
=2) /= 1) call abort()
53 if (ucobound (a
,dim
=2) /= 8) call abort()
55 if (this_image(a
,dim
=3) /= 4) call abort()
56 if (lcobound (a
,dim
=3) /= 4) call abort()
57 if (ucobound (a
,dim
=3) /= 4) call abort()
59 if (any(this_image(a
) /= [-4, 1, 4])) call abort()
60 if (any(lcobound (a
) /= [-4, 1, 4])) call abort()
61 if (any(ucobound (a
) /= [9, 8, 4])) call abort()
64 subroutine three(n
,A
, n2
)
69 if (A(1) /= 42) call abort()
71 if (A(1)[n2
] /= -42) call abort()
73 if (this_image(A
,dim
=1) /= n
) call abort()
74 if (lcobound (A
,dim
=1) /= n
) call abort()
75 if (ucobound (A
,dim
=1) /= n
) call abort()
77 if (any(this_image(A
) /= n
)) call abort()
78 if (any(lcobound (A
) /= n
)) call abort()
79 if (any(ucobound (A
) /= n
)) call abort()
82 subroutine three_a(n
,A
)
84 integer :: A(3)[n
+2:n
+5,n
-1:*]
87 if (A(1) /= 42) call abort()
89 if (A(1)[4,n
] /= -42) call abort()
91 if (this_image(A
,dim
=1) /= n
+2) call abort()
92 if (lcobound (A
,dim
=1) /= n
+2) call abort()
93 if (ucobound (A
,dim
=1) /= n
+5) call abort()
95 if (this_image(A
,dim
=2) /= n
-1) call abort()
96 if (lcobound (A
,dim
=2) /= n
-1) call abort()
97 if (ucobound (A
,dim
=2) /= n
-1) call abort()
99 if (any(this_image(A
) /= [n
+2,n
-1])) call abort()
100 if (any(lcobound (A
) /= [n
+2,n
-1])) call abort()
101 if (any(ucobound (A
) /= [n
+5,n
-1])) call abort()
102 end subroutine three_a
104 subroutine three_b(n
,A
)
106 integer :: A(-1:3,0:4,-2:5,-4:7)[n
+2:n
+5,n
-1:*]
109 if (A(-1,0,-2,-4) /= 42) call abort()
111 if (A(1,0,-2,-4) /= 99) call abort()
113 if (this_image(A
,dim
=1) /= n
+2) call abort()
114 if (lcobound (A
,dim
=1) /= n
+2) call abort()
115 if (ucobound (A
,dim
=1) /= n
+5) call abort()
117 if (this_image(A
,dim
=2) /= n
-1) call abort()
118 if (lcobound (A
,dim
=2) /= n
-1) call abort()
119 if (ucobound (A
,dim
=2) /= n
-1) call abort()
121 if (any(this_image(A
) /= [n
+2,n
-1])) call abort()
122 if (any(lcobound (A
) /= [n
+2,n
-1])) call abort()
123 if (any(ucobound (A
) /= [n
+5,n
-1])) call abort()
124 end subroutine three_b
127 integer, allocatable
:: A(:)[:]
128 if (this_image(A
,dim
=1) /= -4_8) call abort()
129 if (lcobound (A
,dim
=1) /= -4_8) call abort()
130 if (ucobound (A
,dim
=1) /= -4_8) call abort()
134 integer, save :: foo(2)[5:7,4:*]
139 if (foo(1)[5,4] /= 42) call abort()
140 if (this_image(foo
,dim
=i
) /= 5) call abort()
141 if (lcobound(foo
,dim
=i
) /= 5) call abort()
142 if (ucobound(foo
,dim
=i
) /= 7) call abort()
145 if (this_image(foo
,dim
=i
) /= 4) call abort()
146 if (lcobound(foo
,dim
=i
) /= 4) call abort()
147 if (ucobound(foo
,dim
=i
) /= 4) call abort()