OSDN Git Service

2010-04-06 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / coarray_6.f90
1 ! { dg-do compile }
2 !
3 ! Coarray support -- corank declarations
4 ! PR fortran/18918
5 !
6 module m2
7   use iso_c_binding
8   integer(c_int), bind(C) :: a[*] ! { dg-error "BIND.C. attribute conflicts with CODIMENSION" }
9
10   type, bind(C) :: t ! { dg-error "cannot have the ALLOCATABLE" }
11     integer(c_int), allocatable :: a[:] ! { dg-error "cannot have the ALLOCATABLE" }
12     integer(c_int)  :: b[*] ! { dg-error "must be allocatable" }
13   end type t
14 end module m2
15
16 subroutine bind(a) bind(C) ! { dg-error "Coarray dummy variable" }
17   use iso_c_binding
18   integer(c_int) :: a[*]
19 end subroutine bind
20
21 subroutine allo(x) ! { dg-error "can thus not be an allocatable coarray" }
22   integer, allocatable, intent(out) :: x[:]
23 end subroutine allo
24
25 module m
26   integer :: modvar[*] ! OK, implicit save
27   type t
28     complex, allocatable :: b(:,:,:,:)[:,:,:]
29   end type t
30 end module m
31
32 subroutine bar()
33   integer, parameter :: a[*] = 4 ! { dg-error "PARAMETER attribute conflicts with CODIMENSION" }
34   integer, pointer :: b[:] ! { dg-error "is not ALLOCATABLE, SAVE nor a dummy" }
35 end subroutine bar
36
37 subroutine vol()
38   integer,save :: a[*]
39   block
40     volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }
41   end block
42 contains
43   subroutine int()
44     volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }
45   end subroutine int
46 end subroutine vol
47
48
49 function func() result(func2) ! { dg-error "shall not be a coarray or have a coarray component" }
50   use m
51   type(t) :: func2
52 end function func
53
54 program main
55   integer :: A[*] ! Valid, implicit SAVE attribute
56 end program main
57
58 ! { dg-final { cleanup-modules "m" } }