OSDN Git Service

2010-04-06 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / coarray_4.f90
1 ! { dg-do compile }
2 !
3 ! Coarray support -- corank declarations
4 ! PR fortran/18918
5 !
6
7 subroutine valid(n, c, f)
8   implicit none
9   integer :: n
10   integer, save :: a[*], b(4)[-1:4,*]
11   real :: c(*)[1,0:3,3:*]
12   real :: f(n)[0:n,-100:*]
13   integer, allocatable :: d[:], e(:)[:,:]
14   integer, save, codimension[1,*] :: g, h(7), i(6)[*], j[*]
15   integer :: k
16   codimension :: k[*]
17   save :: k
18   integer :: ii = 7
19   block
20     integer, save :: kk[ii, *] ! { dg-error "cannot have the SAVE attribute" }
21   end block
22 end subroutine valid
23
24 subroutine valid2()
25   type t
26     integer, allocatable :: a[:]
27   end type t
28   type, extends(t) :: tt
29     integer, allocatable :: b[:]
30   end type tt
31   type(tt), save :: foo
32   type(tt) :: bar ! { dg-error "is a coarray or has a coarray component" }
33 end subroutine valid2
34
35 subroutine invalid(n)
36   implicit none
37   integer :: n
38   integer :: k[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }
39   integer :: h(3)[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }
40   integer, save :: a[*]
41   codimension :: a[1,*] ! { dg-error "Duplicate CODIMENSION attribute" }
42   complex, save :: hh(n)[*] ! { dg-error "cannot have the SAVE attribute" }
43   integer :: j = 6
44
45   integer, save :: hf1[j,*] ! { dg-error "cannot appear in the expression|cannot have the SAVE attribute" }
46   integer, save :: hf2[n,*] ! { dg-error "cannot have the SAVE attribute" }
47   integer, save :: hf3(4)[j,*] ! { dg-error "cannot appear in the expression|cannot have the SAVE attribute" }
48   integer, save :: hf4(5)[n,*] ! { dg-error "cannot have the SAVE attribute" }
49
50   integer, allocatable :: a2[*] ! { dg-error "must have deferred shape" }
51   integer, allocatable :: a3(:)[*] ! { dg-error "must have deferred shape" }
52   integer, allocatable :: a4[*] ! { dg-error "must have deferred shape" }
53 end subroutine invalid
54
55 subroutine invalid2
56   use iso_c_binding
57   implicit none
58   type t0
59     integer, allocatable :: a[:,:,:]
60   end type t0
61   type t
62   end type t
63   type, extends(t) :: tt ! { dg-error "has a coarray component, parent type" }
64     integer, allocatable :: a[:]
65   end type tt
66   type ttt
67     integer, pointer :: a[:] ! { dg-error "must be allocatable" }
68   end type ttt
69   type t4
70     integer, allocatable :: b[4,*] ! { dg-error "with deferred shape" }
71   end type t4
72   type t5
73     type(c_ptr), allocatable :: p[:] ! { dg-error "shall not be a coarray" }
74   end type t5
75   type(t0), save :: t0_1[*] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }
76   type(t0), allocatable :: t0_2[:] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }
77   type(c_ptr), save :: pp[*] ! { dg-error "shall not be a coarray" }
78 end subroutine invalid2
79
80 elemental subroutine elem(a) ! { dg-error "Coarray dummy argument" }
81   integer, intent(in) :: a[*]
82 end subroutine
83
84 function func() result(res)
85   integer :: res[*] ! { dg-error "CODIMENSION attribute conflicts with RESULT" }
86 end function func