aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/gomp/udr7.f90
blob: 230a3fc44dd967a7d1562971a721439534eaa4f1 (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
! { dg-do compile }

module udr7m1
  type dt
    real :: r
  end type dt
end module udr7m1
module udr7m2
  use udr7m1
  interface operator(+)
    module procedure addm2
  end interface
!$omp declare reduction(+:dt:omp_out=omp_out+omp_in) &
!$omp & initializer(omp_priv=dt(0.0))
!$omp declare reduction(.myadd.:dt:omp_out=omp_out.myadd.omp_in) &
!$omp & initializer(omp_priv=dt(0.0))
  interface operator(.myadd.)
    module procedure addm2
  end interface
  private
  public :: operator(+), operator(.myadd.), dt
contains
  type(dt) function addm2 (x, y)
    type(dt), intent (in):: x, y
    addm2%r = x%r + y%r
  end function
end module udr7m2
module udr7m3
  use udr7m1
  private
  public :: operator(.myadd.), operator(+), dt
  interface operator(.myadd.)
    module procedure addm3
  end interface
!$omp declare reduction(+:dt:omp_out=omp_out+omp_in) &
!$omp & initializer(omp_priv=dt(0.0))
!$omp declare reduction(.myadd.:dt:omp_out=omp_out.myadd.omp_in) &
!$omp & initializer(omp_priv=dt(0.0))
  interface operator(+)
    module procedure addm3
  end interface
contains
  type(dt) function addm3 (x, y)
    type(dt), intent (in):: x, y
    addm3%r = x%r + y%r
  end function
end module udr7m3
module udr7m4
  use udr7m1
  private
  interface operator(.myadd.)
    module procedure addm4
  end interface
!$omp declare reduction(+:dt:omp_out=omp_out+omp_in) &
!$omp & initializer(omp_priv=dt(0.0))
!$omp declare reduction(.myadd.:dt:omp_out=omp_out.myadd.omp_in) &
!$omp & initializer(omp_priv=dt(0.0))
  interface operator(+)
    module procedure addm4
  end interface
contains
  type(dt) function addm4 (x, y)
    type(dt), intent (in):: x, y
    addm4%r = x%r + y%r
  end function
end module udr7m4
subroutine f1
  use udr7m2
  type(dt) :: d, e
  integer :: i
  d=dt(0.0)
  e = dt (0.0)
!$omp parallel do reduction (+ : d) reduction ( .myadd. : e)
  do i=1,100
    d=d+dt(i)
    e=e+dt(i)
  end do
end subroutine f1
subroutine f2
  use udr7m3	! { dg-error "Previous !.OMP DECLARE REDUCTION|Ambiguous interfaces" }
  use udr7m2	! { dg-error "Ambiguous !.OMP DECLARE REDUCTION" }
end subroutine f2
subroutine f3
  use udr7m4
  use udr7m2
end subroutine f3
subroutine f4
  use udr7m3
  use udr7m4
end subroutine f4