OSDN Git Service

2011-12-19 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / coarray_poly_3.f90
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
3 !
4
5
6 subroutine cont1(x) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape array" }
7   type t
8   end type t
9   class(t), contiguous, allocatable :: x(:)
10 end
11
12 subroutine cont2(x) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape array" }
13   type t
14   end type t
15   class(t), contiguous, allocatable :: x(:)[:]
16 end
17
18 subroutine cont3(x, y)
19   type t
20   end type t
21   class(t), contiguous, pointer :: x(:)
22   class(t), contiguous :: y(:)
23 end
24
25 function func() ! { dg-error "shall not be a coarray or have a coarray component" }
26   type t
27   end type t
28   class(t), allocatable :: func[*] ! { dg-error ""
29 end
30
31 function func2() ! { dg-error "must be dummy, allocatable or pointer" }
32   type t
33     integer, allocatable :: caf[:]
34   end type t
35   class(t) :: func2a ! { dg-error "CLASS variable 'func2a' at .1. must be dummy, allocatable or pointer" }
36   class(t) :: func2 ! {CLASS variable 'func' at (1) must be dummy, allocatable or pointer
37 end
38
39 subroutine foo1(x1) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
40   type t
41   end type t
42   type(t) :: x1(:)[:]
43 end
44
45 subroutine foo2(x2) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
46   type t
47   end type t
48   type(t) :: x2[:]
49 end
50
51
52 ! DITTO FOR CLASS
53
54 subroutine foo3(x1) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
55   type t
56   end type t
57   class(t) :: x1(:)[:]
58 end
59
60 subroutine foo4(x2) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
61   type t
62   end type t
63   class(t) :: x2[:]
64 end
65
66
67
68
69 subroutine bar1(y1) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
70   type t
71   end type t
72   type(t), allocatable :: y1(:)[5:*]
73 end
74
75 subroutine bar2(y2) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
76   type t
77   end type t
78   type(t), allocatable :: y2[5:*]
79 end
80
81 subroutine bar3(z1) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
82   type t
83   end type t
84   type(t), allocatable :: z1(5)[:]
85 end
86
87 subroutine bar4(z2) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
88   type t
89   end type t
90   type(t), allocatable :: z2(5)
91 end subroutine bar4
92
93 subroutine bar5(z3) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
94   type t
95   end type t
96   type(t), pointer :: z3(5)
97 end subroutine bar5
98
99
100
101
102 ! DITTO FOR CLASS
103
104 subroutine bar1c(y1) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
105   type t
106   end type t
107   class(t), allocatable :: y1(:)[5:*]
108 end
109
110 subroutine bar2c(y2) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
111   type t
112   end type t
113   class(t), allocatable :: y2[5:*]
114 end
115
116 subroutine bar3c(z1) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
117   type t
118   end type t
119   class(t), allocatable :: z1(5)[:]
120 end
121
122 subroutine bar4c(z2) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
123   type t
124   end type t
125   class(t), allocatable :: z2(5)
126 end subroutine bar4c
127
128 subroutine bar5c(z3) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
129   type t
130   end type t
131   class(t), pointer :: z3(5)
132 end subroutine bar5c
133
134
135 subroutine sub()
136   type t
137   end type
138   type(t) :: a(5)
139   class(t), allocatable :: b(:)
140   call inter(a)
141   call inter(b)
142 contains
143   subroutine inter(x)
144     class(t) :: x(5)
145   end subroutine inter
146 end subroutine sub
147
148 subroutine sub2()
149   type t
150   end type
151   type(t) :: a(5)
152 contains
153   subroutine inter(x)
154     class(t) :: x(5)
155   end subroutine inter
156 end subroutine sub2
157
158 subroutine sub3()
159   type t
160   end type
161 contains
162   subroutine inter2(x) ! { dg-error "must have a deferred shape" }
163     class(t), pointer :: x(5)
164   end subroutine inter2
165 end subroutine sub3