
I noticed that GCC/Rust recently lost all LTO variants in torture testing: PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O0 (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O1 (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O2 (test for excess errors) -PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O2 -flto -fno-use-linker-plugin -flto-partition=none (test for excess errors) -PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O2 -flto -fuse-linker-plugin -fno-fat-lto-objects (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O3 -g (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -Os (test for excess errors) Etc. The reason is that when probing for availability of LTO, we run into: spawn [...]/build-gcc/gcc/testsuite/rust/../../gccrs -B[...]/build-gcc/gcc/testsuite/rust/../../ -fdiagnostics-plain-output -frust-incomplete-and-experimental-compiler-do-not-use -flto -c -o lto8274.o lto8274.c cc1: warning: command-line option '-frust-incomplete-and-experimental-compiler-do-not-use' is valid for Rust but not for C For GCC/Rust testing, this flag is (as of recently) defaulted in 'gcc/testsuite/lib/rust.exp:rust_init': lappend ALWAYS_RUSTFLAGS "additional_flags=-frust-incomplete-and-experimental-compiler-do-not-use" A few more "command-line option [...] is valid for [...] but not for [...]" instances were found in the test suite logs, when more than one language is involved. With '-Wno-complain-wrong-lang' used in 'gcc/testsuite/lib/target-supports.exp:check_compile', we get back: PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O0 (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O1 (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O2 (test for excess errors) +PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O2 -flto -fno-use-linker-plugin -flto-partition=none (test for excess errors) +PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O2 -flto -fuse-linker-plugin -fno-fat-lto-objects (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -O3 -g (test for excess errors) PASS: rust/compile/torture/all_doc_comment_line_blocks.rs -Os (test for excess errors) Etc., and in total: === rust Summary for unix === # of expected passes [-4990-]{+6718+} # of expected failures [-39-]{+51+} Anything that 'gcc/opts-global.cc:complain_wrong_lang' might do is cut short by '-Wno-complain-wrong-lang', not just the one 'warning' diagnostic. This corresponds to what already exists via 'lang_hooks.complain_wrong_lang_p'. The 'gcc/opts-common.cc:prune_options' changes follow the same rationale as PR67640 "driver passes -fdiagnostics-color= always last": we need to process '-Wno-complain-wrong-lang' early, so that it properly affects other options appearing before it on the command line. gcc/ * common.opt (-Wcomplain-wrong-lang): New. * doc/invoke.texi (-Wno-complain-wrong-lang): Document it. * opts-common.cc (prune_options): Handle it. * opts-global.cc (complain_wrong_lang): Use it. gcc/testsuite/ * gcc.dg/Wcomplain-wrong-lang-1.c: New. * gcc.dg/Wcomplain-wrong-lang-2.c: Likewise. * gcc.dg/Wcomplain-wrong-lang-3.c: Likewise. * gcc.dg/Wcomplain-wrong-lang-4.c: Likewise. * gcc.dg/Wcomplain-wrong-lang-5.c: Likewise. * lib/target-supports.exp (check_compile): Use '-Wno-complain-wrong-lang'. * g++.dg/abi/empty12.C: Likewise. * g++.dg/abi/empty13.C: Likewise. * g++.dg/abi/empty14.C: Likewise. * g++.dg/abi/empty15.C: Likewise. * g++.dg/abi/empty16.C: Likewise. * g++.dg/abi/empty17.C: Likewise. * g++.dg/abi/empty18.C: Likewise. * g++.dg/abi/empty19.C: Likewise. * g++.dg/abi/empty22.C: Likewise. * g++.dg/abi/empty25.C: Likewise. * g++.dg/abi/empty26.C: Likewise. * gfortran.dg/bind-c-contiguous-1.f90: Likewise. * gfortran.dg/bind-c-contiguous-4.f90: Likewise. * gfortran.dg/bind-c-contiguous-5.f90: Likewise. libgomp/ * testsuite/libgomp.fortran/alloc-10.f90: Use '-Wno-complain-wrong-lang'. * testsuite/libgomp.fortran/alloc-11.f90: Likewise. * testsuite/libgomp.fortran/alloc-7.f90: Likewise. * testsuite/libgomp.fortran/alloc-9.f90: Likewise. * testsuite/libgomp.fortran/allocate-1.f90: Likewise. * testsuite/libgomp.fortran/depend-4.f90: Likewise. * testsuite/libgomp.fortran/depend-5.f90: Likewise. * testsuite/libgomp.fortran/depend-6.f90: Likewise. * testsuite/libgomp.fortran/depend-7.f90: Likewise. * testsuite/libgomp.fortran/depend-inoutset-1.f90: Likewise. * testsuite/libgomp.fortran/examples-4/declare_target-1.f90: Likewise. * testsuite/libgomp.fortran/examples-4/declare_target-2.f90: Likewise. * testsuite/libgomp.fortran/order-reproducible-1.f90: Likewise. * testsuite/libgomp.fortran/order-reproducible-2.f90: Likewise. * testsuite/libgomp.oacc-fortran/parallel-dims.f90: Likewise. * testsuite/libgomp.fortran/task-detach-6.f90: Remove left-over 'dg-prune-output'.
149 lines
5.9 KiB
Fortran
149 lines
5.9 KiB
Fortran
! OpenACC parallelism dimensions clauses: num_gangs, num_workers,
|
|
! vector_length.
|
|
|
|
! { dg-additional-sources parallel-dims-aux.c }
|
|
! { dg-additional-options -Wno-complain-wrong-lang }
|
|
! { dg-do run }
|
|
|
|
! { dg-additional-options "-DEXPENSIVE" { target run_expensive_tests } }
|
|
! { dg-additional-options "-cpp" }
|
|
|
|
! { dg-additional-options "-fopt-info-note-omp" }
|
|
! { dg-additional-options "--param=openacc-privatization=noisy" }
|
|
! { dg-additional-options "-foffload=-fopt-info-note-omp" }
|
|
! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
|
|
! for testing/documenting aspects of that functionality.
|
|
|
|
! { dg-additional-options "-Wopenacc-parallelism" } for testing/documenting
|
|
! aspects of that functionality.
|
|
|
|
! See also '../libgomp.oacc-c-c++-common/parallel-dims.c'.
|
|
|
|
module acc_routines
|
|
implicit none (type, external)
|
|
|
|
interface
|
|
integer function acc_gang() bind(C)
|
|
!$acc routine seq
|
|
end function acc_gang
|
|
|
|
integer function acc_worker() bind(C)
|
|
!$acc routine seq
|
|
end function acc_worker
|
|
|
|
integer function acc_vector() bind(C)
|
|
!$acc routine seq
|
|
end function acc_vector
|
|
end interface
|
|
end module acc_routines
|
|
|
|
program main
|
|
use iso_c_binding
|
|
use openacc
|
|
use acc_routines
|
|
implicit none (type, external)
|
|
|
|
integer :: gangs_min, gangs_max, workers_min, workers_max, vectors_min, vectors_max
|
|
integer :: vectors_actual
|
|
integer :: i, j, k
|
|
|
|
|
|
#ifdef EXPENSIVE
|
|
integer, parameter :: N = 100
|
|
#else
|
|
integer, parameter :: N = 50
|
|
#endif
|
|
|
|
call acc_init (acc_device_default)
|
|
|
|
! OpenACC parallel construct.
|
|
|
|
!TODO
|
|
|
|
|
|
! OpenACC kernels construct.
|
|
|
|
!TODO
|
|
|
|
|
|
! OpenACC serial construct.
|
|
|
|
! GR, WS, VS.
|
|
|
|
gangs_min = huge(gangs_min) ! INT_MAX
|
|
workers_min = huge(workers_min) ! INT_MAX
|
|
vectors_min = huge(vectors_min) ! INT_MAX
|
|
gangs_max = -huge(gangs_max) - 1 ! INT_MIN
|
|
workers_max = -huge(gangs_max) - 1 ! INT_MIN
|
|
vectors_max = -huge(gangs_max) - 1 ! INT_MIN
|
|
!$acc serial &
|
|
!$acc reduction (min: gangs_min, workers_min, vectors_min) reduction (max: gangs_max, workers_max, vectors_max) ! { dg-warning "using .vector_length \\(32\\)., ignoring 1" "" { target openacc_nvidia_accel_selected } }
|
|
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do i = N, -(N-1), -1
|
|
gangs_min = acc_gang ();
|
|
gangs_max = acc_gang ();
|
|
workers_min = acc_worker ();
|
|
workers_max = acc_worker ();
|
|
vectors_min = acc_vector ();
|
|
vectors_max = acc_vector ();
|
|
end do
|
|
!$acc end serial
|
|
if (gangs_min /= 0 .or. gangs_max /= 1 - 1 &
|
|
.or. workers_min /= 0 .or. workers_max /= 1 - 1 &
|
|
.or. vectors_min /= 0 .or. vectors_max /= 1 - 1) &
|
|
stop 1
|
|
|
|
! Composition of GP, WP, VP.
|
|
|
|
vectors_actual = 1 ! Implicit 'vector_length (1)' clause.
|
|
gangs_min = huge(gangs_min) ! INT_MAX
|
|
workers_min = huge(workers_min) ! INT_MAX
|
|
vectors_min = huge(vectors_min) ! INT_MAX
|
|
gangs_max = -huge(gangs_max) - 1 ! INT_MIN
|
|
workers_max = -huge(gangs_max) - 1 ! INT_MIN
|
|
vectors_max = -huge(gangs_max) - 1 ! INT_MIN
|
|
!$acc serial copy (vectors_actual) &
|
|
!$acc copy (gangs_min, gangs_max, workers_min, workers_max, vectors_min, vectors_max) ! { dg-warning "using .vector_length \\(32\\)., ignoring 1" "" { target openacc_nvidia_accel_selected } }
|
|
! { dg-bogus "\[Ww\]arning: region contains gang partitioned code but is not gang partitioned" "TODO 'serial'" { xfail *-*-* } .-1 }
|
|
! { dg-bogus "\[Ww\]arning: region contains worker partitioned code but is not worker partitioned" "TODO 'serial'" { xfail *-*-* } .-2 }
|
|
! { dg-bogus "\[Ww\]arning: region contains vector partitioned code but is not vector partitioned" "TODO 'serial'" { xfail *-*-* } .-3 }
|
|
! { dg-note {variable 'C.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } .-4 }
|
|
!TODO Unhandled 'CONST_DECL' instance for constant argument in 'acc_on_device' call.
|
|
if (acc_on_device (acc_device_nvidia)) then
|
|
! The GCC nvptx back end enforces vector_length (32).
|
|
! It's unclear if that's actually permissible here;
|
|
! <https://github.com/OpenACC/openacc-spec/issues/238> "OpenACC 'serial'
|
|
! construct might not actually be serial".
|
|
vectors_actual = 32
|
|
end if
|
|
!$acc loop gang reduction (min: gangs_min, workers_min, vectors_min) reduction (max: gangs_max, workers_max, vectors_max)
|
|
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do i = N, -(N-1), -1
|
|
!$acc loop worker reduction (min: gangs_min, workers_min, vectors_min) reduction (max: gangs_max, workers_max, vectors_max)
|
|
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
|
|
do j = N, -(N-1), -1
|
|
!$acc loop vector reduction (min: gangs_min, workers_min, vectors_min) reduction (max: gangs_max, workers_max, vectors_max)
|
|
! { dg-note {variable 'k' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do k = N * vectors_actual, -(N-1) * vectors_actual, -1
|
|
gangs_min = acc_gang ();
|
|
gangs_max = acc_gang ();
|
|
workers_min = acc_worker ();
|
|
workers_max = acc_worker ();
|
|
vectors_min = acc_vector ();
|
|
vectors_max = acc_vector ();
|
|
end do
|
|
end do
|
|
end do
|
|
!$acc end serial
|
|
if (acc_get_device_type () .eq. acc_device_nvidia) then
|
|
if (vectors_actual /= 32) stop 2
|
|
else
|
|
if (vectors_actual /= 1) stop 3
|
|
end if
|
|
if (gangs_min /= 0 .or. gangs_max /= 1 - 1 &
|
|
.or. workers_min /= 0 .or. workers_max /= 1 - 1 &
|
|
.or. vectors_min /= 0 .or. vectors_max /= vectors_actual - 1) &
|
|
stop 4
|
|
|
|
end program main
|