gcc/libgomp/testsuite/libgomp.fortran/depend-6.f90
Thomas Schwinge 320dc51c2d Add '-Wno-complain-wrong-lang', and use it in 'gcc/testsuite/lib/target-supports.exp:check_compile' and elsewhere
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'.
2023-02-22 09:19:51 +01:00

132 lines
3.2 KiB
Fortran

! { dg-additional-sources my-usleep.c }
! { dg-additional-options -Wno-complain-wrong-lang }
module m
use omp_lib
implicit none
interface
subroutine usleep(t) bind(C, name="my_usleep")
use iso_c_binding
integer(c_int), value :: t
end subroutine
end interface
contains
subroutine test (ifval)
logical, value :: ifval
integer :: a(0:7), b(0:7), i
integer(omp_depend_kind) d1, d2
!$omp depobj (d1) depend(inout: omp_all_memory)
!$omp depobj (d2) depend(out: omp_all_memory)
do i = 0, 7
a(i) = i
b(i) = 2 * i
end do
!$omp parallel
block
!$omp single
block
!$omp task shared(a) depend(in: a(0))
block
call usleep (5000)
a(0) = 42
end block
!$omp task shared(a) depend(out: a(1))
block
call usleep (5000)
a(1) = 43
end block
!$omp task shared(a) depend(inout: a(2))
block
call usleep (5000)
a(2) = 44
end block
!$omp task shared(a) depend(mutexinoutset: a(3))
block
call usleep (5000)
a(3) = 45
end block
!$omp task shared(a)
block
call usleep (15000)
a(4) = 46
end block
!$omp task shared(b) depend(in: b(0))
block
call usleep (5000)
b(0) = 47
end block
!$omp task shared(b) depend(in: b(4))
block
call usleep (5000)
b(4) = 48
end block
!$omp task shared(b) depend(inoutset: b(5))
block
call usleep (5000)
b(5) = 49
end block
! None of the above tasks depend on each other.
! The following task depends on all but the a(4) = 46; one.
!$omp task shared(a, b) depend(depobj: d1) private(i) if(ifval)
block
if (a(0) /= 42 .or. a(1) /= 43 .or. a(2) /= 44 .or. a(3) /= 45 &
.or. a(5) /= 5 .or. a(6) /= 6 .or. a(7) /= 7 &
.or. b(0) /= 47 .or. b(1) /= 2 .or. b(2) /= 4 .or. b(3) /= 6 &
.or. b(4) /= 48 .or. b(5) /= 49 .or. b(6) /= 12 .or. b(7) /= 14) &
error stop
do i = 0, 7
if (i /= 4) &
a(i) = 3 * i + 7
end do
do i = 0, 7
b(i) = 4 * i - 7
end do
end block
! The following task depends on both b(0) = 47; and
! above omp_all_memory tasks, but as the latter depends on
! the former, effectively it is dependent just on the omp_all_memory
! task.
!$omp task shared(b) depend(inout: b(0))
block
call usleep (5000)
b(0) = 49
end block
! The following task depends on all the above except a(4) = 46; one,
! but it can be reduced to dependency on the above omp_all_memory
! one and b(0) = 49; one.
!$omp task shared(a, b) depend(inout: b(6)) depend(depobj: d2) &
!$omp& depend(out: b(7)) private(i) if(ifval)
block
do i = 0, 7
if (i /= 4) then
if (a(i) /= 3 * i + 7) &
error stop
a(i) = 5 * i + 50
end if
end do
if (b(0) /= 49) &
error stop
b(0) = 6 * i + 57
do i = 1, 7
if (b(i) /= 4 * i - 7) &
error stop
b(i) = 6 * i + 57
end do
end block
!$omp taskwait
if (a(4) /= 46) &
error stop
end block
end block
!$omp depobj (d2) destroy
!$omp depobj (d1) destroy
end
end module m
use m
call test (.true.)
call test (.false.)
end