Retro68/gcc/libgomp/testsuite/libgomp.oacc-fortran/reduction-4.f90

113 lines
2.1 KiB
Fortran
Raw Normal View History

2015-08-28 15:33:40 +00:00
! { dg-do run }
! complex reductions
program reduction_4
implicit none
2017-04-10 11:32:00 +00:00
integer, parameter :: n = 10, ng = 8, nw = 4, vl = 32
2015-08-28 15:33:40 +00:00
integer :: i
2017-04-10 11:32:00 +00:00
real :: vresult, rg, rw, rv, rc
2015-08-28 15:33:40 +00:00
complex, dimension (n) :: array
do i = 1, n
array(i) = i
end do
2017-04-10 11:32:00 +00:00
!
! '+' reductions
!
rg = 0
rw = 0
rv = 0
rc = 0
2015-08-28 15:33:40 +00:00
vresult = 0
2017-04-10 11:32:00 +00:00
!$acc parallel num_gangs(ng) copy(rg)
!$acc loop reduction(+:rg) gang
do i = 1, n
rg = rg + REAL(array(i))
end do
!$acc end parallel
!$acc parallel num_workers(nw) copy(rw)
!$acc loop reduction(+:rw) worker
do i = 1, n
rw = rw + REAL(array(i))
end do
!$acc end parallel
!$acc parallel vector_length(vl) copy(rv)
!$acc loop reduction(+:rv) vector
do i = 1, n
rv = rv + REAL(array(i))
end do
!$acc end parallel
2015-08-28 15:33:40 +00:00
2017-04-10 11:32:00 +00:00
!$acc parallel num_gangs(ng) num_workers(nw) vector_length(vl) copy(rc)
!$acc loop reduction(+:rc) gang worker vector
2015-08-28 15:33:40 +00:00
do i = 1, n
2017-04-10 11:32:00 +00:00
rc = rc + REAL(array(i))
2015-08-28 15:33:40 +00:00
end do
!$acc end parallel
! Verify the results
do i = 1, n
2017-04-10 11:32:00 +00:00
vresult = vresult + REAL(array(i))
2015-08-28 15:33:40 +00:00
end do
2018-12-28 15:30:48 +00:00
if (rg .ne. vresult) STOP 1
if (rw .ne. vresult) STOP 2
if (rv .ne. vresult) STOP 3
if (rc .ne. vresult) STOP 4
2015-08-28 15:33:40 +00:00
2017-04-10 11:32:00 +00:00
!
! '*' reductions
!
rg = 1
rw = 1
rv = 1
rc = 1
2015-08-28 15:33:40 +00:00
vresult = 1
2017-04-10 11:32:00 +00:00
!$acc parallel num_gangs(ng) copy(rg)
!$acc loop reduction(*:rg) gang
do i = 1, n
rg = rg * REAL(array(i))
end do
!$acc end parallel
!$acc parallel num_workers(nw) copy(rw)
!$acc loop reduction(*:rw) worker
do i = 1, n
rw = rw * REAL(array(i))
end do
!$acc end parallel
!$acc parallel vector_length(vl) copy(rv)
!$acc loop reduction(*:rv) vector
do i = 1, n
rv = rv * REAL(array(i))
end do
!$acc end parallel
!$acc parallel num_gangs(ng) num_workers(nw) vector_length(vl) copy(rc)
!$acc loop reduction(*:rc) gang worker vector
do i = 1, n
rc = rc * REAL(array(i))
end do
!$acc end parallel
! Verify the results
do i = 1, n
vresult = vresult * REAL(array(i))
end do
2018-12-28 15:30:48 +00:00
if (rg .ne. vresult) STOP 5
if (rw .ne. vresult) STOP 6
if (rv .ne. vresult) STOP 7
if (rc .ne. vresult) STOP 8
2015-08-28 15:33:40 +00:00
end program reduction_4