
... including "note: '[...]' was declared here" emitted since recent
commit 9695e1c23b
"Improve -Wuninitialized note location".
For those that seemed incorrect to me, I've placed XFAILed 'dg-bogus'es,
including one more instance of PR77504 etc., and several instances where
for "local variables" of reference-data-type reductions (etc.?) we emit
bogus (?) diagnostics.
For implicit data clauses (including 'firstprivate'), we seem to be missing
diagnostics, so I've placed XFAILed 'dg-warning's.
gcc/testsuite/
* c-c++-common/goacc/builtin-goacc-parlevel-id-size.c: Document
current '-Wuninitialized' diagnostics.
* c-c++-common/goacc/mdc-1.c: Likewise.
* c-c++-common/goacc/nested-reductions-1-kernels.c: Likewise.
* c-c++-common/goacc/nested-reductions-1-parallel.c: Likewise.
* c-c++-common/goacc/nested-reductions-1-routine.c: Likewise.
* c-c++-common/goacc/nested-reductions-2-kernels.c: Likewise.
* c-c++-common/goacc/nested-reductions-2-parallel.c: Likewise.
* c-c++-common/goacc/nested-reductions-2-routine.c: Likewise.
* c-c++-common/goacc/uninit-dim-clause.c: Likewise.
* c-c++-common/goacc/uninit-firstprivate-clause.c: Likewise.
* c-c++-common/goacc/uninit-if-clause.c: Likewise.
* gfortran.dg/goacc/array-with-dt-1.f90: Likewise.
* gfortran.dg/goacc/array-with-dt-2.f90: Likewise.
* gfortran.dg/goacc/array-with-dt-3.f90: Likewise.
* gfortran.dg/goacc/array-with-dt-4.f90: Likewise.
* gfortran.dg/goacc/array-with-dt-5.f90: Likewise.
* gfortran.dg/goacc/derived-chartypes-1.f90: Likewise.
* gfortran.dg/goacc/derived-chartypes-2.f90: Likewise.
* gfortran.dg/goacc/derived-chartypes-3.f90: Likewise.
* gfortran.dg/goacc/derived-chartypes-4.f90: Likewise.
* gfortran.dg/goacc/derived-classtypes-1.f95: Likewise.
* gfortran.dg/goacc/derived-types-2.f90: Likewise.
* gfortran.dg/goacc/host_data-tree.f95: Likewise.
* gfortran.dg/goacc/kernels-tree.f95: Likewise.
* gfortran.dg/goacc/modules.f95: Likewise.
* gfortran.dg/goacc/nested-reductions-1-kernels.f90: Likewise.
* gfortran.dg/goacc/nested-reductions-1-parallel.f90: Likewise.
* gfortran.dg/goacc/nested-reductions-1-routine.f90: Likewise.
* gfortran.dg/goacc/nested-reductions-2-kernels.f90: Likewise.
* gfortran.dg/goacc/nested-reductions-2-parallel.f90: Likewise.
* gfortran.dg/goacc/nested-reductions-2-routine.f90: Likewise.
* gfortran.dg/goacc/parallel-tree.f95: Likewise.
* gfortran.dg/goacc/pr93464.f90: Likewise.
* gfortran.dg/goacc/privatization-1-compute-loop.f90: Likewise.
* gfortran.dg/goacc/privatization-1-compute.f90: Likewise.
* gfortran.dg/goacc/privatization-1-routine_gang-loop.f90:
Likewise.
* gfortran.dg/goacc/privatization-1-routine_gang.f90: Likewise.
* gfortran.dg/goacc/uninit-dim-clause.f95: Likewise.
* gfortran.dg/goacc/uninit-firstprivate-clause.f95: Likewise.
* gfortran.dg/goacc/uninit-if-clause.f95: Likewise.
* gfortran.dg/goacc/uninit-use-device-clause.f95: Likewise.
* gfortran.dg/goacc/wait.f90: Likewise.
libgomp/
* testsuite/libgomp.oacc-c-c++-common/vred2d-128.c: Document
current '-Wuninitialized' diagnostics.
* testsuite/libgomp.oacc-fortran/data-5.f90: Likewise.
* testsuite/libgomp.oacc-fortran/gemm-2.f90: Likewise.
* testsuite/libgomp.oacc-fortran/gemm.f90: Likewise.
* testsuite/libgomp.oacc-fortran/optional-reduction.f90: Likewise.
* testsuite/libgomp.oacc-fortran/parallel-reduction.f90: Likewise.
* testsuite/libgomp.oacc-fortran/pr70643.f90: Likewise.
* testsuite/libgomp.oacc-fortran/pr96628-part1.f90: Likewise.
* testsuite/libgomp.oacc-fortran/privatized-ref-2.f90: Likewise.
* testsuite/libgomp.oacc-fortran/reduction-5.f90: Likewise.
* testsuite/libgomp.oacc-fortran/reduction-7.f90: Likewise.
* testsuite/libgomp.oacc-fortran/reference-reductions.f90:
Likewise.
81 lines
2.3 KiB
Fortran
81 lines
2.3 KiB
Fortran
! Test optional arguments in reduction clauses. The effect of
|
|
! non-present arguments in reduction clauses is undefined, and is not tested
|
|
! for. The tests are based on those in reduction-1.f90.
|
|
|
|
! { dg-do run }
|
|
|
|
! { dg-additional-options -Wuninitialized }
|
|
|
|
!TODO
|
|
! { dg-xfail-run-if TODO { openacc_radeon_accel_selected && { ! __OPTIMIZE__ } } }
|
|
|
|
program optional_reduction
|
|
implicit none
|
|
|
|
integer :: rg, rw, rv, rc
|
|
|
|
rg = 0
|
|
rw = 0
|
|
rv = 0
|
|
rc = 0
|
|
|
|
call do_test(rg, rw, rv, rc)
|
|
contains
|
|
subroutine do_test(rg, rw, rv, rc)
|
|
integer, parameter :: n = 10, ng = 8, nw = 4, vl = 32
|
|
integer, optional :: rg, rw, rv, rc
|
|
integer :: i, vresult
|
|
integer, dimension (n) :: array
|
|
|
|
vresult = 0
|
|
do i = 1, n
|
|
array(i) = i
|
|
end do
|
|
|
|
!$acc parallel num_gangs(ng) copy(rg)
|
|
!$acc loop reduction(+:rg) gang
|
|
! { dg-bogus {'rg\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
|
|
! { dg-note {'rg\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
|
|
do i = 1, n
|
|
rg = rg + array(i)
|
|
end do
|
|
!$acc end parallel
|
|
|
|
!$acc parallel num_workers(nw) copy(rw)
|
|
!$acc loop reduction(+:rw) worker
|
|
! { dg-bogus {'rw\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
|
|
! { dg-note {'rw\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
|
|
do i = 1, n
|
|
rw = rw + array(i)
|
|
end do
|
|
!$acc end parallel
|
|
|
|
!$acc parallel vector_length(vl) copy(rv)
|
|
!$acc loop reduction(+:rv) vector
|
|
! { dg-bogus {'rv\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
|
|
! { dg-note {'rv\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
|
|
do i = 1, n
|
|
rv = rv + 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
|
|
! { dg-bogus {'rc\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
|
|
! { dg-note {'rc\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
|
|
do i = 1, n
|
|
rc = rc + array(i)
|
|
end do
|
|
!$acc end parallel
|
|
|
|
! Verify the results
|
|
do i = 1, n
|
|
vresult = vresult + array(i)
|
|
end do
|
|
|
|
if (rg .ne. vresult) STOP 1
|
|
if (rw .ne. vresult) STOP 2
|
|
if (rv .ne. vresult) STOP 3
|
|
if (rc .ne. vresult) STOP 4
|
|
end subroutine do_test
|
|
end program optional_reduction
|