aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90
blob: fd46206ea15273ceeedf19a6a61ff8a42819fb1e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
! { dg-do compile }
! { dg-options "-fcoarray=single" }
!


subroutine cont1(x) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape or assumed-rank array" }
  type t
  end type t
  class(t), contiguous, allocatable :: x(:)
end

subroutine cont2(x) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape or assumed-rank array" }
  type t
  end type t
  class(t), contiguous, allocatable :: x(:)[:]
end

subroutine cont3(x, y)
  type t
  end type t
  class(t), contiguous, pointer :: x(:)
  class(t), contiguous :: y(:)
end

function func() ! { dg-error "shall not be a coarray or have a coarray component" }
  type t
  end type t
  class(t), allocatable :: func[*]
end

function func2() ! { dg-error "must be dummy, allocatable or pointer" }
  type t
    integer, allocatable :: caf[:]
  end type t
  class(t) :: func2a ! { dg-error "CLASS variable 'func2a' at .1. must be dummy, allocatable or pointer" }
  class(t) :: func2
end

subroutine foo1(x1) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
  type t
  end type t
  type(t) :: x1(:)[:]
end

subroutine foo2(x2) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
  type t
  end type t
  type(t) :: x2[:]
end


! DITTO FOR CLASS

subroutine foo3(x1) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
  type t
  end type t
  class(t) :: x1(:)[:]
end

subroutine foo4(x2) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
  type t
  end type t
  class(t) :: x2[:]
end




subroutine bar1(y1) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
  type t
  end type t
  type(t), allocatable :: y1(:)[5:*]
end

subroutine bar2(y2) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
  type t
  end type t
  type(t), allocatable :: y2[5:*]
end

subroutine bar3(z1) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
  type t
  end type t
  type(t), allocatable :: z1(5)[:]
end

subroutine bar4(z2) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
  type t
  end type t
  type(t), allocatable :: z2(5)
end subroutine bar4

subroutine bar5(z3) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
  type t
  end type t
  type(t), pointer :: z3(5)
end subroutine bar5




! DITTO FOR CLASS

subroutine bar1c(y1) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
  type t
  end type t
  class(t), allocatable :: y1(:)[5:*]
end

subroutine bar2c(y2) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
  type t
  end type t
  class(t), allocatable :: y2[5:*]
end

subroutine bar3c(z1) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
  type t
  end type t
  class(t), allocatable :: z1(5)[:]
end

subroutine bar4c(z2) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
  type t
  end type t
  class(t), allocatable :: z2(5)
end subroutine bar4c

subroutine bar5c(z3) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
  type t
  end type t
  class(t), pointer :: z3(5)
end subroutine bar5c


subroutine sub()
  type t
  end type
  type(t) :: a(5)
  class(t), allocatable :: b(:)
  call inter(a)
  call inter(b)
contains
  subroutine inter(x)
    class(t) :: x(5)
  end subroutine inter
end subroutine sub

subroutine sub2()
  type t
  end type
  type(t) :: a(5)
contains
  subroutine inter(x)
    class(t) :: x(5)
  end subroutine inter
end subroutine sub2

subroutine sub3()
  type t
  end type
contains
  subroutine inter2(x) ! { dg-error "must have a deferred shape" }
    class(t), pointer :: x(5)
  end subroutine inter2
end subroutine sub3