3 ! Run-time test for IMAGE_INDEX with cobounds only known at
4 ! the compile time, suitable for any number of NUM_IMAGES()
5 ! For compile-time cobounds, the -fcoarray=lib version still
6 ! needs to run-time evalulation if image_index returns > 1
7 ! as image_index is 0 if the index would exceed num_images().
9 ! Please set num_images() to >= 13, if possible.
14 program test_image_index
16 integer :: index1
, index2
, index3
19 integer, allocatable
:: a(:)[:,:,:], b(:)[:,:], c(:,:)[:]
20 integer, save :: d(2)[-1:3, *]
21 integer, save :: e(2)[-1:-1, 3:*]
23 one
= num_images() == 1
25 allocate(a(1)[3:3, -4:-3, 88:*])
26 allocate(b(2)[-1:0,0:*])
29 index1
= image_index(a
, [3, -4, 88] )
30 index2
= image_index(b
, [-1, 0] )
31 index3
= image_index(c
, [1] )
32 if (index1
/= 1 .or
. index2
/= 1 .or
. index3
/= 1) STOP 1
35 index1
= image_index(a
, [3, -3, 88] )
36 index2
= image_index(b
, [0, 0] )
37 index3
= image_index(c
, [2] )
39 if (one
.and
. (index1
/= 0 .or
. index2
/= 0 .or
. index3
/= 0)) &
41 if (.not
. one
.and
. (index1
/= 2 .or
. index2
/= 2 .or
. index3
/= 2)) &
45 index1
= image_index(d
, [-1, 1] )
46 index2
= image_index(d
, [0, 1] )
48 if (one
.and
. (index1
/= 1 .or
. index2
/= 0)) &
50 if (.not
. one
.and
. (index1
/= 1 .or
. index2
/= 2)) &
53 index1
= image_index(e
, [-1, 3] )
54 index2
= image_index(e
, [-1, 4] )
56 if (one
.and
. (index1
/= 1 .or
. index2
/= 0)) &
58 if (.not
. one
.and
. (index1
/= 1 .or
. index2
/= 2)) &
63 ! The following test is in honour of the F2008 standard:
65 allocate(a (10) [10, 0:9, 0:*])
67 index1
= image_index(a
, [1, 0, 0] )
68 index2
= image_index(a
, [3, 1, 2] ) ! = 213, yeah!
69 index3
= image_index(a
, [3, 1, 0] ) ! = 13
71 if (num_images() < 13 .and
. (index1
/= 1 .or
. index2
/= 0 .or
. index3
/= 0)) &
73 if (num_images() >= 213 .and
. (index1
/= 1 .or
. index2
/= 213 .or
. index3
/= 13)) &
75 if (num_images() >= 13 .and
. (index1
/= 1 .or
. index2
/= 0 .or
. index3
/= 13)) &
80 subroutine test(n
, a
, b
, c
)
82 integer :: a(1)[3*n
:3*n
, -4*n
:-3*n
, 88*n
:*], b(2)[-1*n
:0*n
,0*n
:*], c(3*n
,3*n
)[*]
84 index1
= image_index(a
, [3, -4, 88] )
85 index2
= image_index(b
, [-1, 0] )
86 index3
= image_index(c
, [1] )
87 if (index1
/= 1 .or
. index2
/= 1 .or
. index3
/= 1) STOP 11
90 index1
= image_index(a
, [3, -3, 88] )
91 index2
= image_index(b
, [0, 0] )
92 index3
= image_index(c
, [2] )
94 if (one
.and
. (index1
/= 0 .or
. index2
/= 0 .or
. index3
/= 0)) &
96 if (.not
. one
.and
. (index1
/= 2 .or
. index2
/= 2 .or
. index3
/= 2)) &
99 end program test_image_index