
... 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.
83 lines
1.9 KiB
Fortran
83 lines
1.9 KiB
Fortran
! Exercise three levels of parallelism using SGEMM from BLAS.
|
|
|
|
! { dg-do run }
|
|
|
|
! { dg-additional-options -Wuninitialized }
|
|
|
|
! Explicitly set vector_length to 128 using a vector_length clause.
|
|
subroutine openacc_sgemm_128 (m, n, k, alpha, a, b, beta, c)
|
|
integer :: m, n, k
|
|
real :: alpha, beta
|
|
real :: a(k,*), b(k,*), c(m,*)
|
|
|
|
integer :: i, j, l
|
|
real :: temp
|
|
! { dg-note {'temp' was declared here} {} { target *-*-* } .-1 }
|
|
|
|
!$acc parallel loop copy(c(1:m,1:n)) copyin(a(1:k,1:m),b(1:k,1:n)) vector_length (128) firstprivate (temp)
|
|
! { dg-warning {'temp' is used uninitialized} {} { target *-*-* } .-1 }
|
|
do j = 1, n
|
|
!$acc loop
|
|
do i = 1, m
|
|
temp = 0.0
|
|
!$acc loop reduction(+:temp)
|
|
do l = 1, k
|
|
temp = temp + a(l,i)*b(l,j)
|
|
end do
|
|
if(beta == 0.0) then
|
|
c(i,j) = alpha*temp
|
|
else
|
|
c(i,j) = alpha*temp + beta*c(i,j)
|
|
end if
|
|
end do
|
|
end do
|
|
end subroutine openacc_sgemm_128
|
|
|
|
subroutine host_sgemm (m, n, k, alpha, a, b, beta, c)
|
|
integer :: m, n, k
|
|
real :: alpha, beta
|
|
real :: a(k,*), b(k,*), c(m,*)
|
|
|
|
integer :: i, j, l
|
|
real :: temp
|
|
|
|
do j = 1, n
|
|
do i = 1, m
|
|
temp = 0.0
|
|
do l = 1, k
|
|
temp = temp + a(l,i)*b(l,j)
|
|
end do
|
|
if(beta == 0.0) then
|
|
c(i,j) = alpha*temp
|
|
else
|
|
c(i,j) = alpha*temp + beta*c(i,j)
|
|
end if
|
|
end do
|
|
end do
|
|
end subroutine host_sgemm
|
|
|
|
program main
|
|
integer, parameter :: M = 100, N = 50, K = 2000
|
|
real :: a(K, M), b(K, N), c(M, N), d (M, N), e (M, N)
|
|
real alpha, beta
|
|
integer i, j
|
|
|
|
a(:,:) = 1.0
|
|
b(:,:) = 0.25
|
|
|
|
c(:,:) = 0.0
|
|
d(:,:) = 0.0
|
|
e(:,:) = 0.0
|
|
|
|
alpha = 1.05
|
|
beta = 1.25
|
|
|
|
call openacc_sgemm_128 (M, N, K, alpha, a, b, beta, d)
|
|
call host_sgemm (M, N, K, alpha, a, b, beta, e)
|
|
|
|
do i = 1, m
|
|
do j = 1, n
|
|
if (d(i,j) /= e(i,j)) stop 1
|
|
end do
|
|
end do
|
|
end program main
|