1! { dg-do compile }
2! { dg-additional-options "-fmax-errors=100" }
3
4subroutine foo (ia1)
5integer :: i1, i2, i3
6integer, dimension (*) :: ia1
7integer, dimension (10) :: ia2
8real :: r1
9real, dimension (5) :: ra1
10double precision :: d1
11double precision, dimension (4) :: da1
12complex :: c1
13complex, dimension (7) :: ca1
14logical :: l1
15logical, dimension (3) :: la1
16character (5) :: a1
17type t
18  integer :: i
19end type
20type(t) :: t1
21type(t), dimension (2) :: ta1
22real, pointer :: p1 => NULL()
23integer, allocatable :: aa1 (:,:)
24save i2
25common /blk/ i1
26
27!$acc parallel reduction (+:ia2)
28!$acc end parallel
29!$acc parallel reduction (+:ra1)
30!$acc end parallel
31!$acc parallel reduction (+:ca1)
32!$acc end parallel
33!$acc parallel reduction (+:da1)
34!$acc end parallel
35!$acc parallel reduction (.and.:la1)
36!$acc end parallel
37!$acc parallel reduction (+:i3, r1, d1, c1)
38!$acc end parallel
39!$acc parallel reduction (*:i3, r1, d1, c1)
40!$acc end parallel
41!$acc parallel reduction (-:i3, r1, d1, c1)
42!$acc end parallel
43!$acc parallel reduction (.and.:l1)
44!$acc end parallel
45!$acc parallel reduction (.or.:l1)
46!$acc end parallel
47!$acc parallel reduction (.eqv.:l1)
48!$acc end parallel
49!$acc parallel reduction (.neqv.:l1)
50!$acc end parallel
51!$acc parallel reduction (min:i3, r1, d1)
52!$acc end parallel
53!$acc parallel reduction (max:i3, r1, d1)
54!$acc end parallel
55!$acc parallel reduction (iand:i3)
56!$acc end parallel
57!$acc parallel reduction (ior:i3)
58!$acc end parallel
59!$acc parallel reduction (ieor:i3)
60!$acc end parallel
61!$acc parallel reduction (+:/blk/)	! { dg-error "Syntax error" }
62!$acc end parallel			! { dg-error "Unexpected" }
63!$acc parallel reduction (*:p1)		! { dg-error "POINTER object" }
64!$acc end parallel
65!$acc parallel reduction (-:aa1)
66!$acc end parallel
67!$acc parallel reduction (*:ia1)	! { dg-error "Assumed size" }
68!$acc end parallel
69!$acc parallel reduction (+:l1)		! { dg-error "OMP DECLARE REDUCTION \\+ not found for type LOGICAL" }
70!$acc end parallel
71!$acc parallel reduction (*:la1)	! { dg-error "OMP DECLARE REDUCTION \\* not found for type LOGICAL" }
72!$acc end parallel
73!$acc parallel reduction (-:a1)		! { dg-error "OMP DECLARE REDUCTION - not found for type CHARACTER" }
74!$acc end parallel
75!$acc parallel reduction (+:t1)		! { dg-error "OMP DECLARE REDUCTION \\+ not found for type TYPE" }
76!$acc end parallel
77!$acc parallel reduction (*:ta1)	! { dg-error "OMP DECLARE REDUCTION \\* not found for type TYPE" }
78!$acc end parallel
79!$acc parallel reduction (.and.:i3)	! { dg-error "OMP DECLARE REDUCTION \\.and\\. not found for type INTEGER" }
80!$acc end parallel
81!$acc parallel reduction (.or.:ia2)	! { dg-error "OMP DECLARE REDUCTION \\.or\\. not found for type INTEGER" }
82!$acc end parallel
83!$acc parallel reduction (.eqv.:r1)	! { dg-error "OMP DECLARE REDUCTION \\.eqv\\. not found for type REAL" }
84!$acc end parallel
85!$acc parallel reduction (.neqv.:ra1)	! { dg-error "OMP DECLARE REDUCTION \\.neqv\\. not found for type REAL" }
86!$acc end parallel
87!$acc parallel reduction (.and.:d1)	! { dg-error "OMP DECLARE REDUCTION \\.and\\. not found for type REAL" }
88!$acc end parallel
89!$acc parallel reduction (.or.:da1)	! { dg-error "OMP DECLARE REDUCTION \\.or\\. not found for type REAL" }
90!$acc end parallel
91!$acc parallel reduction (.eqv.:c1)	! { dg-error "OMP DECLARE REDUCTION \\.eqv\\. not found for type COMPLEX" }
92!$acc end parallel
93!$acc parallel reduction (.neqv.:ca1)	! { dg-error "OMP DECLARE REDUCTION \\.neqv\\. not found for type COMPLEX" }
94!$acc end parallel
95!$acc parallel reduction (.and.:a1)	! { dg-error "OMP DECLARE REDUCTION \\.and\\. not found for type CHARACTER" }
96!$acc end parallel
97!$acc parallel reduction (.or.:t1)	! { dg-error "OMP DECLARE REDUCTION \\.or\\. not found for type TYPE" }
98!$acc end parallel
99!$acc parallel reduction (.eqv.:ta1)	! { dg-error "OMP DECLARE REDUCTION \\.eqv\\. not found for type TYPE" }
100!$acc end parallel
101!$acc parallel reduction (min:c1)	! { dg-error "OMP DECLARE REDUCTION min not found for type COMPLEX" }
102!$acc end parallel
103!$acc parallel reduction (max:ca1)	! { dg-error "OMP DECLARE REDUCTION max not found for type COMPLEX" }
104!$acc end parallel
105!$acc parallel reduction (max:l1)	! { dg-error "OMP DECLARE REDUCTION max not found for type LOGICAL" }
106!$acc end parallel
107!$acc parallel reduction (min:la1)	! { dg-error "OMP DECLARE REDUCTION min not found for type LOGICAL" }
108!$acc end parallel
109!$acc parallel reduction (max:a1)	! { dg-error "OMP DECLARE REDUCTION max not found for type CHARACTER" }
110!$acc end parallel
111!$acc parallel reduction (min:t1)	! { dg-error "OMP DECLARE REDUCTION min not found for type TYPE" }
112!$acc end parallel
113!$acc parallel reduction (max:ta1)	! { dg-error "OMP DECLARE REDUCTION max not found for type TYPE" }
114!$acc end parallel
115!$acc parallel reduction (iand:r1)	! { dg-error "OMP DECLARE REDUCTION iand not found for type REAL" }
116!$acc end parallel
117!$acc parallel reduction (ior:ra1)	! { dg-error "OMP DECLARE REDUCTION ior not found for type REAL" }
118!$acc end parallel
119!$acc parallel reduction (ieor:d1)	! { dg-error "OMP DECLARE REDUCTION ieor not found for type REAL" }
120!$acc end parallel
121!$acc parallel reduction (ior:da1)	! { dg-error "OMP DECLARE REDUCTION ior not found for type REAL" }
122!$acc end parallel
123!$acc parallel reduction (iand:c1)	! { dg-error "OMP DECLARE REDUCTION iand not found for type COMPLEX" }
124!$acc end parallel
125!$acc parallel reduction (ior:ca1)	! { dg-error "OMP DECLARE REDUCTION ior not found for type COMPLEX" }
126!$acc end parallel
127!$acc parallel reduction (ieor:l1)	! { dg-error "OMP DECLARE REDUCTION ieor not found for type LOGICAL" }
128!$acc end parallel
129!$acc parallel reduction (iand:la1)	! { dg-error "OMP DECLARE REDUCTION iand not found for type LOGICAL" }
130!$acc end parallel
131!$acc parallel reduction (ior:a1)	! { dg-error "OMP DECLARE REDUCTION ior not found for type CHARACTER" }
132!$acc end parallel
133!$acc parallel reduction (ieor:t1)	! { dg-error "OMP DECLARE REDUCTION ieor not found for type TYPE" }
134!$acc end parallel
135!$acc parallel reduction (iand:ta1)	! { dg-error "OMP DECLARE REDUCTION iand not found for type TYPE" }
136!$acc end parallel
137
138end subroutine
139
140! { dg-error "Array 'ia2' is not permitted in reduction" "" { target "*-*-*" } 27 }
141! { dg-error "Array 'ra1' is not permitted in reduction" "" { target "*-*-*" } 29 }
142! { dg-error "Array 'ca1' is not permitted in reduction" "" { target "*-*-*" } 31 }
143! { dg-error "Array 'da1' is not permitted in reduction" "" { target "*-*-*" } 33 }
144! { dg-error "Array 'la1' is not permitted in reduction" "" { target "*-*-*" } 35 }
145! { dg-error "Array 'aa1' is not permitted in reduction" "" { target "*-*-*" } 65 }
146! { dg-error "Array 'ia1' is not permitted in reduction" "" { target "*-*-*" } 67 }
147! { dg-error "Array 'la1' is not permitted in reduction" "" { target "*-*-*" } 71 }
148! { dg-error "Array 'ta1' is not permitted in reduction" "" { target "*-*-*" } 77 }
149! { dg-error "Array 'ia2' is not permitted in reduction" "" { target "*-*-*" } 81 }
150! { dg-error "Array 'ra1' is not permitted in reduction" "" { target "*-*-*" } 85 }
151! { dg-error "Array 'da1' is not permitted in reduction" "" { target "*-*-*" } 89 }
152! { dg-error "Array 'ca1' is not permitted in reduction" "" { target "*-*-*" } 93 }
153! { dg-error "Array 'ta1' is not permitted in reduction" "" { target "*-*-*" } 99 }
154! { dg-error "Array 'ca1' is not permitted in reduction" "" { target "*-*-*" } 103 }
155! { dg-error "Array 'la1' is not permitted in reduction" "" { target "*-*-*" } 107 }
156! { dg-error "Array 'ta1' is not permitted in reduction" "" { target "*-*-*" } 113 }
157! { dg-error "Array 'ra1' is not permitted in reduction" "" { target "*-*-*" } 117 }
158! { dg-error "Array 'da1' is not permitted in reduction" "" { target "*-*-*" } 121 }
159! { dg-error "Array 'ca1' is not permitted in reduction" "" { target "*-*-*" } 125 }
160! { dg-error "Array 'la1' is not permitted in reduction" "" { target "*-*-*" } 129 }
161! { dg-error "Array 'ta1' is not permitted in reduction" "" { target "*-*-*" } 135 }
162