Rebase.
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / udr5.f90
blob6dae9b9b81642e810571ff9dc26942940582ccd1
1 ! { dg-do run }
3 module m
4 interface operator(.add.)
5 module procedure do_add
6 end interface
7 type dt
8 real :: r = 0.0
9 end type
10 contains
11 function do_add(x, y)
12 type (dt), intent (in) :: x, y
13 type (dt) :: do_add
14 do_add%r = x%r + y%r
15 end function
16 subroutine dp_add(x, y)
17 double precision :: x, y
18 x = x + y
19 end subroutine
20 subroutine dp_init(x)
21 double precision :: x
22 x = 0.0
23 end subroutine
24 end module
26 program udr5
27 use m, only : operator(.add.), dt, dp_add, dp_init
28 type(dt) :: xdt, one
29 real :: r
30 integer (kind = 4) :: i4
31 integer (kind = 8) :: i8
32 real (kind = 4) :: r4
33 double precision :: dp
34 !$omp declare reduction(.add.:dt:omp_out=omp_out.add.omp_in)
35 !$omp declare reduction(foo:integer(4),integer(kind=8),real (kind = 4) &
36 !$omp & :omp_out = omp_out + omp_in) initializer (omp_priv = 0)
37 !$omp declare reduction(foo:double precision:dp_add (omp_out, omp_in)) &
38 !$omp & initializer (dp_init (omp_priv))
40 one%r = 1.0
41 r = 0.0
42 i4 = 0
43 i8 = 0
44 r4 = 0.0
45 call dp_init (dp)
46 !$omp parallel reduction(.add.: xdt) reduction(+: r) &
47 !$omp & reduction(foo: i4, i8, r4, dp)
48 xdt = xdt.add.one
49 r = r + 1.0
50 i4 = i4 + 1
51 i8 = i8 + 1
52 r4 = r4 + 1.0
53 call dp_add (dp, 1.0d0)
54 !$omp end parallel
55 if (xdt%r .ne. r) call abort
56 if (i4.ne.r.or.i8.ne.r.or.r4.ne.r.or.dp.ne.r) call abort
57 end program udr5