OSDN Git Service

2011-09-26 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / coarray_10.f90
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
3 !
4 ! PR fortran/18918
5 !
6 ! Coarray intrinsics
7 !
8
9 subroutine image_idx_test1()
10   INTEGER,save :: array[2,-1:4,8,*]
11   WRITE (*,*) IMAGE_INDEX (array, [2,0,3,1])
12   WRITE (*,*) IMAGE_INDEX (array, [0,0,3,1])  ! { dg-error "for dimension 1, SUB has 0 and COARRAY lower bound is 1" }
13   WRITE (*,*) IMAGE_INDEX (array, [1,2,9,0])  ! { dg-error "for dimension 3, SUB has 9 and COARRAY upper bound is 8" }
14   WRITE (*,*) IMAGE_INDEX (array, [2,0,3])    ! { dg-error "array elements of the SUB argument to IMAGE_INDEX at .1. shall be 4" }
15   WRITE (*,*) IMAGE_INDEX (array, [2,0,3,1,1])! { dg-error "array elements of the SUB argument to IMAGE_INDEX at .1. shall be 4" }
16 end subroutine
17
18 subroutine this_image_check()
19   integer,save :: a(1,2,3,5)[0:3,*]
20   integer :: j
21   integer,save :: z(4)[*], i
22
23   j = this_image(a,dim=3) ! { dg-error "not a valid codimension index" }
24   j = this_image(dim=3) ! { dg-error "DIM argument without ARRAY argument" }
25   i = image_index(i, [ 1 ]) ! { dg-error "Expected coarray variable" }
26   i = image_index(z, 2) ! { dg-error "must be a rank one array" }
27 end subroutine this_image_check
28
29
30 subroutine rank_mismatch()
31   implicit none
32   integer,allocatable :: A(:)[:,:,:,:]
33   allocate(A(1)[1,1,1:*])     ! { dg-error "Unexpected ... for codimension" }
34   allocate(A(1)[1,1,1,1,1,*]) ! { dg-error "Invalid codimension 5" }
35   allocate(A(1)[1,1,1,*])
36   allocate(A(1)[1,1])     ! { dg-error "Too few codimensions" }
37   allocate(A(1)[1,*])     ! { dg-error "Too few codimensions" }
38   allocate(A(1)[1,1:*])   ! { dg-error "Unexpected ... for codimension" }
39
40   A(1)[1,1,1] = 1       ! { dg-error "Too few codimensions" }
41   A(1)[1,1,1,1,1,1] = 1 ! { dg-error "Invalid codimension 5" }
42   A(1)[1,1,1,1] = 1
43   A(1)[1,1] = 1         ! { dg-error "Too few codimensions" }
44   A(1)[1,1] = 1         ! { dg-error "Too few codimensions" }
45   A(1)[1,1:1] = 1       ! { dg-error "Too few codimensions" }
46 end subroutine rank_mismatch
47
48 subroutine rank_mismatch2()
49   implicit none
50   integer, allocatable:: A(:)[:,:,:]
51   allocate(A(1)[7:8,4:*]) ! { dg-error "Unexpected .*. for codimension 2 of 3" }
52 end subroutine rank_mismatch2