OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [gomp/] [reduction1.f90] - Blame information for rev 149

Go to most recent revision | Details | Compare with Previous | View Log

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

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.