annotate gcc/testsuite/gfortran.dg/coarray_poly_3.f90 @ 144:8f4e72ab4e11

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