Rebase.
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / udr6.f90
blob92fc5bb1be53d45ca30c1f3944ef29509caa551c
1 ! { dg-do compile }
2 ! { dg-options "-fmax-errors=1000 -fopenmp -ffree-line-length-160" }
4 module udr6
5 type dt
6 integer :: i
7 end type
8 end module udr6
9 subroutine f1
10 use udr6, only : dt
11 !$omp declare reduction (+:integer:omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
12 !$omp declare reduction (+:real(kind=4):omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
13 !$omp declare reduction (+:double precision:omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
14 !$omp declare reduction (+:integer(kind=8),integer(kind=1) & ! { dg-error "Redefinition of predefined" }
15 !$omp & :omp_out = omp_out + omp_in)
16 !$omp declare reduction (+:complex:omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
17 !$omp declare reduction (+:complex(kind=8):omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
18 interface operator(+)
19 function addf1 (x, y)
20 use udr6, only : dt
21 type(dt), intent (in) :: x, y
22 type(dt) :: addf1
23 end function
24 end interface
25 end subroutine f1
26 subroutine f2
27 use udr6, only : dt
28 interface operator(-)
29 function subf2 (x, y)
30 use udr6, only : dt
31 type(dt), intent (in) :: x, y
32 type(dt) :: subf2
33 end function
34 end interface
35 !$omp declare reduction (-:integer:omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
36 !$omp declare reduction (-:real(kind=4):omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
37 !$omp declare reduction (-:double precision:omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
38 !$omp declare reduction (-:integer(kind=8),integer(kind=1) & ! { dg-error "Redefinition of predefined" }
39 !$omp & :omp_out = omp_out + omp_in)
40 !$omp declare reduction (-:complex:omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
41 !$omp declare reduction (-:complex(kind=8):omp_out = omp_out + omp_in) ! { dg-error "Redefinition of predefined" }
42 end subroutine f2
43 subroutine f3
44 use udr6, only : dt
45 interface operator(*)
46 function mulf3 (x, y)
47 use udr6, only : dt
48 type(dt), intent (in) :: x, y
49 type(dt) :: mulf3
50 end function
51 end interface
52 !$omp declare reduction (*:integer:omp_out = omp_out * omp_in) ! { dg-error "Redefinition of predefined" }
53 !$omp declare reduction (*:real(kind=4):omp_out = omp_out * omp_in) ! { dg-error "Redefinition of predefined" }
54 !$omp declare reduction (*:double precision:omp_out = omp_out * omp_in) ! { dg-error "Redefinition of predefined" }
55 !$omp declare reduction (*:integer(kind=8),integer(kind=1) & ! { dg-error "Redefinition of predefined" }
56 !$omp & :omp_out = omp_out * omp_in)
57 !$omp declare reduction (*:complex:omp_out = omp_out * omp_in) ! { dg-error "Redefinition of predefined" }
58 !$omp declare reduction (*:complex(kind=8):omp_out = omp_out * omp_in) ! { dg-error "Redefinition of predefined" }
59 end subroutine f3
60 subroutine f4
61 use udr6, only : dt
62 interface operator(.and.)
63 function andf4 (x, y)
64 use udr6, only : dt
65 type(dt), intent (in) :: x, y
66 type(dt) :: andf4
67 end function
68 end interface
69 !$omp declare reduction (.neqv.:logical:omp_out = omp_out .or. omp_in) ! { dg-error "Redefinition of predefined" }
70 interface operator(.or.)
71 function orf4 (x, y)
72 use udr6, only : dt
73 type(dt), intent (in) :: x, y
74 type(dt) :: orf4
75 end function
76 end interface
77 !$omp declare reduction (.eqv.:logical:omp_out = omp_out .or. omp_in) ! { dg-error "Redefinition of predefined" }
78 interface operator(.eqv.)
79 function eqvf4 (x, y)
80 use udr6, only : dt
81 type(dt), intent (in) :: x, y
82 type(dt) :: eqvf4
83 end function
84 end interface
85 !$omp declare reduction (.or.:logical:omp_out = omp_out .or. omp_in) ! { dg-error "Redefinition of predefined" }
86 interface operator(.neqv.)
87 function neqvf4 (x, y)
88 use udr6, only : dt
89 type(dt), intent (in) :: x, y
90 type(dt) :: neqvf4
91 end function
92 end interface
93 !$omp declare reduction (.and.:logical:omp_out = omp_out .and. omp_in) ! { dg-error "Redefinition of predefined" }
94 end subroutine f4
95 subroutine f5
96 use udr6, only : dt
97 interface operator(.and.)
98 function andf5 (x, y)
99 use udr6, only : dt
100 type(dt), intent (in) :: x, y
101 type(dt) :: andf5
102 end function
103 end interface
104 !$omp declare reduction (.neqv.:logical(kind =4):omp_out = omp_out .neqv. omp_in) ! { dg-error "Redefinition of predefined" }
105 interface operator(.or.)
106 function orf5 (x, y)
107 use udr6, only : dt
108 type(dt), intent (in) :: x, y
109 type(dt) :: orf5
110 end function
111 end interface
112 !$omp declare reduction (.eqv.:logical(kind= 4):omp_out = omp_out .eqv. omp_in) ! { dg-error "Redefinition of predefined" }
113 interface operator(.eqv.)
114 function eqvf5 (x, y)
115 use udr6, only : dt
116 type(dt), intent (in) :: x, y
117 type(dt) :: eqvf5
118 end function
119 end interface
120 !$omp declare reduction (.or.:logical(kind=4):omp_out = omp_out .or. omp_in) ! { dg-error "Redefinition of predefined" }
121 interface operator(.neqv.)
122 function neqvf5 (x, y)
123 use udr6, only : dt
124 type(dt), intent (in) :: x, y
125 type(dt) :: neqvf5
126 end function
127 end interface
128 !$omp declare reduction (.and.:logical(kind = 4):omp_out = omp_out .and. omp_in) ! { dg-error "Redefinition of predefined" }
129 end subroutine f5
130 subroutine f6
131 !$omp declare reduction (min:integer:omp_out = min (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
132 !$omp declare reduction (max:integer:omp_out = max (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
133 !$omp declare reduction (iand:integer:omp_out = iand (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
134 !$omp declare reduction (ior:integer:omp_out = ior (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
135 !$omp declare reduction (ieor:integer:omp_out = ieor (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
136 !$omp declare reduction (min:real:omp_out = min (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
137 !$omp declare reduction (max:real:omp_out = max (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
138 !$omp declare reduction (min:double precision:omp_out = min (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
139 !$omp declare reduction (max:double precision:omp_out = max (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
140 end subroutine f6
141 subroutine f7
142 !$omp declare reduction (min:integer(kind=2):omp_out = min (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
143 !$omp declare reduction (max:integer(kind=4):omp_out = max (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
144 !$omp declare reduction (iand:integer(kind=1):omp_out = iand (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
145 !$omp declare reduction (ior:integer(kind=8):omp_out = ior (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
146 !$omp declare reduction (ieor:integer(kind=4):omp_out = ieor (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
147 !$omp declare reduction (min:real(kind=4):omp_out = min (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
148 !$omp declare reduction (max:real(kind=4):omp_out = max (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
149 !$omp declare reduction (min:double precision:omp_out = min (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
150 !$omp declare reduction (max:double precision:omp_out = max (omp_out, omp_in)) ! { dg-error "Redefinition of predefined" }
151 end subroutine f7
152 subroutine f8
153 integer :: min
154 !$omp declare reduction (min:integer:omp_out = omp_out + omp_in)
155 !$omp declare reduction (min:real:omp_out = omp_out + omp_in)
156 !$omp declare reduction (min:double precision:omp_out = omp_out + omp_in)
157 end subroutine f8
158 subroutine f9
159 integer :: max
160 !$omp declare reduction (max:integer:omp_out = omp_out + omp_in)
161 !$omp declare reduction (max:real:omp_out = omp_out + omp_in)
162 !$omp declare reduction (max:double precision:omp_out = omp_out + omp_in)
163 end subroutine f9
164 subroutine f10
165 integer :: iand
166 !$omp declare reduction (iand:integer:omp_out = omp_out + omp_in)
167 !$omp declare reduction (iand:real:omp_out = omp_out + omp_in)
168 end subroutine f10
169 subroutine f11
170 integer :: ior
171 !$omp declare reduction (ior:integer:omp_out = omp_out + omp_in)
172 !$omp declare reduction (ior:real:omp_out = omp_out + omp_in)
173 end subroutine f11
174 subroutine f12
175 integer :: ieor
176 !$omp declare reduction (ieor:integer:omp_out = omp_out + omp_in)
177 !$omp declare reduction (ieor:real:omp_out = omp_out + omp_in)
178 end subroutine f12
179 subroutine f13
180 !$omp declare reduction (min:integer:omp_out = omp_out + omp_in)
181 !$omp declare reduction (min:real:omp_out = omp_out + omp_in)
182 !$omp declare reduction (min:double precision:omp_out = omp_out + omp_in)
183 integer :: min
184 end subroutine f13
185 subroutine f14
186 !$omp declare reduction (max:integer:omp_out = omp_out + omp_in)
187 !$omp declare reduction (max:real:omp_out = omp_out + omp_in)
188 !$omp declare reduction (max:double precision:omp_out = omp_out + omp_in)
189 integer :: max
190 end subroutine f14
191 subroutine f15
192 !$omp declare reduction (iand:integer:omp_out = omp_out + omp_in)
193 !$omp declare reduction (iand:real:omp_out = omp_out + omp_in)
194 integer :: iand
195 end subroutine f15
196 subroutine f16
197 !$omp declare reduction (ior:integer:omp_out = omp_out + omp_in)
198 !$omp declare reduction (ior:real:omp_out = omp_out + omp_in)
199 integer :: ior
200 end subroutine f16
201 subroutine f17
202 !$omp declare reduction (ieor:integer:omp_out = omp_out + omp_in)
203 !$omp declare reduction (ieor:real:omp_out = omp_out + omp_in)
204 integer :: ieor
205 end subroutine f17