Dead
[official-gcc.git] / gomp-20050608-branch / gcc / testsuite / gfortran.dg / gomp / reduction1.f90
blobb69714d4b914db0bb592430ffd1c18aabb2dcebe
1 ! { dg-do compile }
2 ! { dg-require-effective-target tls }
4 subroutine foo (ia1)
5 integer :: i1, i2, i3
6 integer, dimension (*) :: ia1
7 integer, dimension (10) :: ia2
8 real :: r1
9 real, dimension (5) :: ra1
10 double precision :: d1
11 double precision, dimension (4) :: da1
12 complex :: c1
13 complex, dimension (7) :: ca1
14 logical :: l1
15 logical, dimension (3) :: la1
16 character (5) :: a1
17 type t
18 integer :: i
19 end type
20 type(t) :: t1
21 type(t), dimension (2) :: ta1
22 real, pointer :: p1 => NULL()
23 integer, allocatable :: aa1 (:,:)
24 save i2
25 !$omp threadprivate (i2)
26 common /blk/ i1
28 !$omp parallel reduction (+:i3, ia2, r1, ra1, d1, da1, c1, ca1)
29 !$omp end parallel
30 !$omp parallel reduction (*:i3, ia2, r1, ra1, d1, da1, c1, ca1)
31 !$omp end parallel
32 !$omp parallel reduction (-:i3, ia2, r1, ra1, d1, da1, c1, ca1)
33 !$omp end parallel
34 !$omp parallel reduction (.and.:l1, la1)
35 !$omp end parallel
36 !$omp parallel reduction (.or.:l1, la1)
37 !$omp end parallel
38 !$omp parallel reduction (.eqv.:l1, la1)
39 !$omp end parallel
40 !$omp parallel reduction (.neqv.:l1, la1)
41 !$omp end parallel
42 !$omp parallel reduction (min:i3, ia2, r1, ra1, d1, da1)
43 !$omp end parallel
44 !$omp parallel reduction (max:i3, ia2, r1, ra1, d1, da1)
45 !$omp end parallel
46 !$omp parallel reduction (iand:i3, ia2)
47 !$omp end parallel
48 !$omp parallel reduction (ior:i3, ia2)
49 !$omp end parallel
50 !$omp parallel reduction (ieor:i3, ia2)
51 !$omp end parallel
52 !$omp parallel reduction (+:/blk/) ! { dg-error "Syntax error" }
53 !$omp end parallel ! { dg-error "Unexpected" }
54 !$omp parallel reduction (+:i2) ! { dg-error "THREADPRIVATE object" }
55 !$omp end parallel
56 !$omp parallel reduction (*:p1) ! { dg-error "POINTER object" }
57 !$omp end parallel
58 !$omp parallel reduction (-:aa1) ! { dg-error "is ALLOCATABLE" }
59 !$omp end parallel
60 !$omp parallel reduction (*:ia1) ! { dg-error "Assumed size" }
61 !$omp end parallel
62 !$omp parallel reduction (+:l1) ! { dg-error "is LOGICAL" }
63 !$omp end parallel
64 !$omp parallel reduction (*:la1) ! { dg-error "is LOGICAL" }
65 !$omp end parallel
66 !$omp parallel reduction (-:a1) ! { dg-error "is CHARACTER" }
67 !$omp end parallel
68 !$omp parallel reduction (+:t1) ! { dg-error "is TYPE" }
69 !$omp end parallel
70 !$omp parallel reduction (*:ta1) ! { dg-error "is TYPE" }
71 !$omp end parallel
72 !$omp parallel reduction (.and.:i3) ! { dg-error "must be LOGICAL" }
73 !$omp end parallel
74 !$omp parallel reduction (.or.:ia2) ! { dg-error "must be LOGICAL" }
75 !$omp end parallel
76 !$omp parallel reduction (.eqv.:r1) ! { dg-error "must be LOGICAL" }
77 !$omp end parallel
78 !$omp parallel reduction (.neqv.:ra1) ! { dg-error "must be LOGICAL" }
79 !$omp end parallel
80 !$omp parallel reduction (.and.:d1) ! { dg-error "must be LOGICAL" }
81 !$omp end parallel
82 !$omp parallel reduction (.or.:da1) ! { dg-error "must be LOGICAL" }
83 !$omp end parallel
84 !$omp parallel reduction (.eqv.:c1) ! { dg-error "must be LOGICAL" }
85 !$omp end parallel
86 !$omp parallel reduction (.neqv.:ca1) ! { dg-error "must be LOGICAL" }
87 !$omp end parallel
88 !$omp parallel reduction (.and.:a1) ! { dg-error "must be LOGICAL" }
89 !$omp end parallel
90 !$omp parallel reduction (.or.:t1) ! { dg-error "must be LOGICAL" }
91 !$omp end parallel
92 !$omp parallel reduction (.eqv.:ta1) ! { dg-error "must be LOGICAL" }
93 !$omp end parallel
94 !$omp parallel reduction (min:c1) ! { dg-error "must be INTEGER or REAL" }
95 !$omp end parallel
96 !$omp parallel reduction (max:ca1) ! { dg-error "must be INTEGER or REAL" }
97 !$omp end parallel
98 !$omp parallel reduction (max:l1) ! { dg-error "must be INTEGER or REAL" }
99 !$omp end parallel
100 !$omp parallel reduction (min:la1) ! { dg-error "must be INTEGER or REAL" }
101 !$omp end parallel
102 !$omp parallel reduction (max:a1) ! { dg-error "must be INTEGER or REAL" }
103 !$omp end parallel
104 !$omp parallel reduction (min:t1) ! { dg-error "must be INTEGER or REAL" }
105 !$omp end parallel
106 !$omp parallel reduction (max:ta1) ! { dg-error "must be INTEGER or REAL" }
107 !$omp end parallel
108 !$omp parallel reduction (iand:r1) ! { dg-error "must be INTEGER" }
109 !$omp end parallel
110 !$omp parallel reduction (ior:ra1) ! { dg-error "must be INTEGER" }
111 !$omp end parallel
112 !$omp parallel reduction (ieor:d1) ! { dg-error "must be INTEGER" }
113 !$omp end parallel
114 !$omp parallel reduction (ior:da1) ! { dg-error "must be INTEGER" }
115 !$omp end parallel
116 !$omp parallel reduction (iand:c1) ! { dg-error "must be INTEGER" }
117 !$omp end parallel
118 !$omp parallel reduction (ior:ca1) ! { dg-error "must be INTEGER" }
119 !$omp end parallel
120 !$omp parallel reduction (ieor:l1) ! { dg-error "must be INTEGER" }
121 !$omp end parallel
122 !$omp parallel reduction (iand:la1) ! { dg-error "must be INTEGER" }
123 !$omp end parallel
124 !$omp parallel reduction (ior:a1) ! { dg-error "must be INTEGER" }
125 !$omp end parallel
126 !$omp parallel reduction (ieor:t1) ! { dg-error "must be INTEGER" }
127 !$omp end parallel
128 !$omp parallel reduction (iand:ta1) ! { dg-error "must be INTEGER" }
129 !$omp end parallel
131 end subroutine