gcc/libgomp/testsuite/libgomp.fortran/alloc-9.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

198 lines
6.3 KiB
Fortran

! { dg-additional-sources alloc-7.c }
! { dg-additional-options -Wno-complain-wrong-lang }
module m
use omp_lib
use iso_c_binding
implicit none
type (omp_alloctrait), parameter :: traits2(*) &
= [ omp_alloctrait (omp_atk_alignment, 16), &
omp_alloctrait (omp_atk_sync_hint, omp_atv_default), &
omp_alloctrait (omp_atk_access, omp_atv_default), &
omp_alloctrait (omp_atk_pool_size, 1024), &
omp_alloctrait (omp_atk_fallback, omp_atv_default_mem_fb), &
omp_alloctrait (omp_atk_partition, omp_atv_environment)]
type (omp_alloctrait) :: traits3(7) &
= [ omp_alloctrait (omp_atk_sync_hint, omp_atv_uncontended), &
omp_alloctrait (omp_atk_alignment, 32), &
omp_alloctrait (omp_atk_access, omp_atv_all), &
omp_alloctrait (omp_atk_pool_size, 512), &
omp_alloctrait (omp_atk_fallback, omp_atv_allocator_fb), &
omp_alloctrait (omp_atk_fb_data, 0), &
omp_alloctrait (omp_atk_partition, omp_atv_default)]
type (omp_alloctrait), parameter :: traits4(*) &
= [ omp_alloctrait (omp_atk_alignment, 128), &
omp_alloctrait (omp_atk_pool_size, 1024), &
omp_alloctrait (omp_atk_fallback, omp_atv_null_fb)]
interface
integer(c_int) function get__alignof_int () bind(C)
import :: c_int
end
end interface
end module m
program main
use m
implicit none (external, type)
type(c_ptr), volatile :: p, q, r
integer, pointer, contiguous, volatile :: ip(:), iq(:), ir(:)
type (omp_alloctrait) :: traits(3)
integer (omp_allocator_handle_kind) :: a, a2
integer (c_ptrdiff_t) :: iptr
integer :: i
traits = [ omp_alloctrait (omp_atk_alignment, 64), &
omp_alloctrait (omp_atk_fallback, omp_atv_null_fb), &
omp_alloctrait (omp_atk_pool_size, 4096)]
p = omp_calloc (3_c_size_t, sizeof (0), omp_default_mem_alloc)
call c_f_pointer (p, ip, [3])
if (mod (TRANSFER (p, iptr), get__alignof_int ()) /= 0 &
.or. ip(1) /= 0 .or. ip(2) /= 0 .or. ip(3) /= 0) &
stop 1
ip(1) = 1
ip(2) = 2
ip(3) = 3
call omp_free (p, omp_default_mem_alloc)
p = omp_calloc (2_c_size_t, sizeof (0), omp_default_mem_alloc)
call c_f_pointer (p, ip, [2])
if (mod (TRANSFER (p, iptr), get__alignof_int ()) /= 0 &
.or. ip(1) /= 0 .or. ip(2) /= 0) &
stop 2
ip(1) = 1
ip(2) = 2
call omp_free (p, omp_null_allocator)
call omp_set_default_allocator (omp_default_mem_alloc)
p = omp_calloc (1_c_size_t, sizeof (0), omp_null_allocator)
call c_f_pointer (p, ip, [1])
if (mod (TRANSFER (p, iptr), get__alignof_int ()) /= 0 &
.or. ip(1) /= 0) &
stop 3
ip(1) = 3
call omp_free (p, omp_get_default_allocator ())
a = omp_init_allocator (omp_default_mem_space, 3, traits)
if (a == omp_null_allocator) &
stop 4
p = omp_calloc (3_c_size_t, 1024_c_size_t, a)
call c_f_pointer (p, ip, [3072 / c_sizeof (0)])
if (mod (TRANSFER (p, iptr), 64) /= 0) &
stop 5
do i = 1, 3072 / c_sizeof (0)
if (ip(i) /= 0) &
stop 6
end do
ip(1) = 1
ip(3072 / c_sizeof (0)) = 2
if (c_associated (omp_calloc (1024_c_size_t, 3_c_size_t, a))) &
stop 7
call omp_free (p, a)
p = omp_calloc (512_c_size_t, 6_c_size_t, a)
call c_f_pointer (p, ip, [3072 / c_sizeof (0)])
do i = 1, 3072 / c_sizeof (0)
if (ip(i) /= 0) &
stop 8
end do
ip(1) = 3
ip(3072 / c_sizeof (0)) = 4
call omp_free (p, omp_null_allocator)
call omp_set_default_allocator (a)
if (omp_get_default_allocator () /= a) &
stop 9
p = omp_calloc (12_c_size_t, 256_c_size_t, omp_null_allocator)
call c_f_pointer (p, ip, [3072 / c_sizeof (0)])
do i = 1, 3072 / c_sizeof (0)
if (ip(i) /= 0) &
stop 10
end do
if (c_associated (omp_calloc (128_c_size_t, 24_c_size_t, omp_null_allocator))) &
stop 11
call omp_free (p, a)
call omp_destroy_allocator (a)
a = omp_init_allocator (omp_default_mem_space, size (traits2), traits2)
if (a == omp_null_allocator) &
stop 12
if (traits3(6)%key /= omp_atk_fb_data) &
stop 13
traits3(6)%value = a
a2 = omp_init_allocator (omp_default_mem_space, size (traits3), traits3)
if (a2 == omp_null_allocator) &
stop 14
p = omp_calloc (10_c_size_t, 42_c_size_t, a2)
call c_f_pointer (p, ip, [420 / c_sizeof (0)])
do i = 1, 420 / c_sizeof (0)
if (ip(i) /= 0) &
stop 15
end do
if (mod (TRANSFER (p, iptr), 32) /= 0) &
stop 16
ip(1) = 5
ip(420 / c_sizeof (0)) = 6
q = omp_calloc (24_c_size_t, 32_c_size_t, a2)
call c_f_pointer (q, iq, [768 / c_sizeof (0)])
if (mod (TRANSFER (q, iptr), 16) /= 0) &
stop 17
do i = 1, 768 / c_sizeof (0)
if (iq(i) /= 0) &
stop 18
end do
iq(1) = 7
iq(768 / c_sizeof (0)) = 8
r = omp_calloc (128_c_size_t, 4_c_size_t, a2)
call c_f_pointer (r, ir, [512 / c_sizeof (0)])
if (mod (TRANSFER (r, iptr), get__alignof_int ()) /= 0) &
stop 19
do i = 1, 512 / c_sizeof (0)
if (ir(i) /= 0) &
stop 20
end do
ir(1) = 9
ir(512 / c_sizeof (0)) = 10
call omp_free (p, omp_null_allocator)
call omp_free (q, a2)
call omp_free (r, omp_null_allocator)
call omp_destroy_allocator (a2)
call omp_destroy_allocator (a)
a = omp_init_allocator (omp_default_mem_space, size (traits4), traits4)
if (a == omp_null_allocator) &
stop 21
if (traits3(6)%key /= omp_atk_fb_data) &
stop 22
traits3(6)%value = a
a2 = omp_init_allocator (omp_default_mem_space, size (traits3), traits3)
if (a2 == omp_null_allocator) &
stop 23
call omp_set_default_allocator (a2)
p = omp_calloc (42_c_size_t, 10_c_size_t, omp_null_allocator)
call c_f_pointer (p, ip, [420 / c_sizeof (0)])
if (mod (TRANSFER (p, iptr), 32) /= 0) &
stop 24
do i = 1, 420 / c_sizeof (0)
if (ip(i) /= 0) &
stop 25
end do
ip(1) = 5
ip(420 / c_sizeof (0)) = 6
q = omp_calloc (32_c_size_t, 24_c_size_t, omp_null_allocator)
call c_f_pointer (q, iq, [768 / c_sizeof (0)])
if (mod (TRANSFER (q, iptr), 128) /= 0) &
stop 26
do i = 1, 768 / c_sizeof (0)
if (iq(i) /= 0) &
stop 27
end do
iq(1) = 7
iq(768 / c_sizeof (0)) = 8
if (c_associated (omp_calloc (24_c_size_t, 32_c_size_t, omp_null_allocator))) &
stop 28
call omp_free (p, omp_null_allocator)
call omp_free (q, omp_null_allocator)
call omp_free (c_null_ptr, omp_null_allocator)
call omp_free (c_null_ptr, omp_null_allocator)
call omp_destroy_allocator (a2)
call omp_destroy_allocator (a)
end program main