OpenMP: Reject non-const 'condition' trait in Fortran

OpenMP 5.0 only permits constant expressions for the 'condition' trait
in context selectors; this is relaxed in 5.2 but not implemented. In order
to avoid wrong code, it is now rejected.

Additionally, in Fortran, 'condition' should not accept an integer
expression, which is now ensured. Additionally, as 'device_num' should be
a conforming device number, there is now a check on the value.

	PR middle-end/113904

gcc/c/ChangeLog:

	* c-parser.cc (c_parser_omp_context_selector): Handle splitting of
	OMP_TRAIT_PROPERTY_EXPR into OMP_TRAIT_PROPERTY_{DEV_NUM,BOOL}_EXPR.

gcc/cp/ChangeLog:

	* parser.cc (cp_parser_omp_context_selector): Handle splitting of
	OMP_TRAIT_PROPERTY_EXPR into OMP_TRAIT_PROPERTY_{DEV_NUM,BOOL}_EXPR.

gcc/fortran/ChangeLog:

	* trans-openmp.cc (gfc_trans_omp_declare_variant): Handle splitting of
	OMP_TRAIT_PROPERTY_EXPR into OMP_TRAIT_PROPERTY_{DEV_NUM,BOOL}_EXPR.
	* openmp.cc (gfc_match_omp_context_selector): Likewise; rejects
	non-const device_num/condition; improve diagnostic.

gcc/ChangeLog:

	* omp-general.cc (struct omp_ts_info): Update for splitting of
	OMP_TRAIT_PROPERTY_EXPR into OMP_TRAIT_PROPERTY_{DEV_NUM,BOOL}_EXPR.
	* omp-selectors.h (enum omp_tp_type): Replace
	OMP_TRAIT_PROPERTY_EXPR by OMP_TRAIT_PROPERTY_{DEV_NUM,BOOL}_EXPR.

gcc/testsuite/ChangeLog:

	* gfortran.dg/gomp/declare-variant-1.f90: Change 'condition' trait's
	argument from integer to a logical expression.
	* gfortran.dg/gomp/declare-variant-11.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-12.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-13.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-2.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-2a.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-3.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-4.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-6.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-8.f90: Likewise.
	* gfortran.dg/gomp/declare-variant-20.f90: New test.
This commit is contained in:
Tobias Burnus 2024-02-13 20:55:26 +01:00
parent 0eb9265fe7
commit a5d34b60c9
17 changed files with 119 additions and 44 deletions

View file

@ -24656,7 +24656,8 @@ c_parser_omp_context_selector (c_parser *parser, enum omp_tss_code set,
}
while (1);
break;
case OMP_TRAIT_PROPERTY_EXPR:
case OMP_TRAIT_PROPERTY_DEV_NUM_EXPR:
case OMP_TRAIT_PROPERTY_BOOL_EXPR:
t = c_parser_expr_no_commas (parser, NULL).value;
if (t != error_mark_node)
{

View file

@ -47984,7 +47984,8 @@ cp_parser_omp_context_selector (cp_parser *parser, enum omp_tss_code set,
}
while (1);
break;
case OMP_TRAIT_PROPERTY_EXPR:
case OMP_TRAIT_PROPERTY_DEV_NUM_EXPR:
case OMP_TRAIT_PROPERTY_BOOL_EXPR:
/* FIXME: this is bogus, the expression need
not be constant. */
t = cp_parser_constant_expression (parser);

View file

@ -5790,19 +5790,39 @@ gfc_match_omp_context_selector (gfc_omp_set_selector *oss)
}
while (1);
break;
case OMP_TRAIT_PROPERTY_EXPR:
case OMP_TRAIT_PROPERTY_DEV_NUM_EXPR:
case OMP_TRAIT_PROPERTY_BOOL_EXPR:
if (gfc_match_expr (&otp->expr) != MATCH_YES)
{
gfc_error ("expected expression at %C");
return MATCH_ERROR;
}
if (!gfc_resolve_expr (otp->expr)
|| (otp->expr->ts.type != BT_LOGICAL
|| (property_kind == OMP_TRAIT_PROPERTY_BOOL_EXPR
&& otp->expr->ts.type != BT_LOGICAL)
|| (property_kind == OMP_TRAIT_PROPERTY_DEV_NUM_EXPR
&& otp->expr->ts.type != BT_INTEGER)
|| otp->expr->rank != 0)
|| otp->expr->rank != 0
|| otp->expr->expr_type != EXPR_CONSTANT)
{
gfc_error ("property must be constant integer or logical "
"expression at %C");
if (property_kind == OMP_TRAIT_PROPERTY_BOOL_EXPR)
gfc_error ("property must be a constant logical expression "
"at %C");
else
gfc_error ("property must be a constant integer expression "
"at %C");
return MATCH_ERROR;
}
/* Device number must be conforming, which includes
omp_initial_device (-1) and omp_invalid_device (-4). */
if (property_kind == OMP_TRAIT_PROPERTY_DEV_NUM_EXPR
&& otp->expr->expr_type == EXPR_CONSTANT
&& mpz_sgn (otp->expr->value.integer) < 0
&& mpz_cmp_si (otp->expr->value.integer, -1) != 0
&& mpz_cmp_si (otp->expr->value.integer, -4) != 0)
{
gfc_error ("property must be a conforming device number "
"at %C");
return MATCH_ERROR;
}
break;

View file

@ -8426,7 +8426,8 @@ gfc_trans_omp_declare_variant (gfc_namespace *ns)
{
switch (otp->property_kind)
{
case OMP_TRAIT_PROPERTY_EXPR:
case OMP_TRAIT_PROPERTY_DEV_NUM_EXPR:
case OMP_TRAIT_PROPERTY_BOOL_EXPR:
{
gfc_se se;
gfc_init_se (&se, NULL);

View file

@ -1163,7 +1163,7 @@ struct omp_ts_info omp_ts_map[] =
},
{ "device_num",
(1 << OMP_TRAIT_SET_TARGET_DEVICE),
OMP_TRAIT_PROPERTY_EXPR, false,
OMP_TRAIT_PROPERTY_DEV_NUM_EXPR, false,
NULL
},
{ "vendor",
@ -1208,7 +1208,7 @@ struct omp_ts_info omp_ts_map[] =
},
{ "condition",
(1 << OMP_TRAIT_SET_USER),
OMP_TRAIT_PROPERTY_EXPR, true,
OMP_TRAIT_PROPERTY_BOOL_EXPR, true,
NULL
},
{ "target",

View file

@ -64,7 +64,8 @@ enum omp_tp_type {
OMP_TRAIT_PROPERTY_NONE,
OMP_TRAIT_PROPERTY_ID,
OMP_TRAIT_PROPERTY_NAME_LIST,
OMP_TRAIT_PROPERTY_EXPR,
OMP_TRAIT_PROPERTY_DEV_NUM_EXPR,
OMP_TRAIT_PROPERTY_BOOL_EXPR,
OMP_TRAIT_PROPERTY_CLAUSE_LIST,
OMP_TRAIT_PROPERTY_EXTENSION
};

View file

@ -20,11 +20,11 @@ module main
!$omp & match (construct={parallel,do}, &
!$omp & device={isa(avx512f,avx512vl),kind(host,cpu)}, &
!$omp & implementation={vendor(score(0):gnu),unified_shared_memory}, &
!$omp & user={condition(score(0):0)})
!$omp & user={condition(score(0):.false.)})
!$omp declare variant (bar) &
!$omp & match (device={arch(x86_64,powerpc64),isa(avx512f,popcntb)}, &
!$omp & implementation={atomic_default_mem_order(seq_cst),made_up_selector("foo", 13, "bar")}, &
!$omp & user={condition(3-3)})
!$omp & user={condition(.true. .AND. (.not. .true.))})
! { dg-warning "unknown selector 'made_up_selector'" "" { target *-*-* } .-2 }
end function

View file

@ -49,8 +49,8 @@ contains
subroutine f13 ()
!$omp declare variant (f10) match (device={isa("avx512f")})
!$omp declare variant (f11) match (user={condition(1)},device={isa(avx512f)},implementation={vendor(gnu)})
!$omp declare variant (f12) match (user={condition(2 + 1)},device={isa(avx512f)})
!$omp declare variant (f11) match (user={condition(.true.)},device={isa(avx512f)},implementation={vendor(gnu)})
!$omp declare variant (f12) match (user={condition(.true. .NEQV. .false.)},device={isa(avx512f)})
end subroutine
subroutine f14 ()

View file

@ -17,7 +17,7 @@ contains
subroutine f04 ()
!$omp declare variant (f01) match (device={isa("avx512f","avx512vl")}) ! 16
!$omp declare variant (f02) match (implementation={vendor(score(15):gnu)})
!$omp declare variant (f03) match (user={condition(score(11):1)})
!$omp declare variant (f03) match (user={condition(score(11):.true.)})
end subroutine
subroutine f05 ()
@ -32,7 +32,7 @@ contains
subroutine f08 ()
!$omp declare variant (f05) match (device={isa(avx512f,avx512vl)}) ! 16
!$omp declare variant (f06) match (implementation={vendor(score(15):gnu)})
!$omp declare variant (f07) match (user={condition(score(17):1)})
!$omp declare variant (f07) match (user={condition(score(17):.true.)})
end subroutine
subroutine f09 ()
@ -48,7 +48,7 @@ contains
end subroutine
subroutine f13 ()
!$omp declare variant (f09) match (device={arch(x86_64)},user={condition(score(65):1)}) ! 64+65
!$omp declare variant (f09) match (device={arch(x86_64)},user={condition(score(65):.true.)}) ! 64+65
!$omp declare variant (f10) match (implementation={vendor(score(127):"gnu")})
!$omp declare variant (f11) match (device={isa(ssse3)}) ! 128
!$omp declare variant (f12) match (implementation={atomic_default_mem_order(score(126):seq_cst)})
@ -65,7 +65,7 @@ contains
subroutine f17 ()
!$omp declare variant (f14) match (construct={teams,parallel,do}) ! 16+8+4
!$omp declare variant (f15) match (construct={parallel},user={condition(score(19):1)}) ! 8+19
!$omp declare variant (f15) match (construct={parallel},user={condition(score(19):.true.)}) ! 8+19
!$omp declare variant (f16) match (implementation={atomic_default_mem_order(score(27):seq_cst)})
end subroutine
@ -80,7 +80,7 @@ contains
subroutine f21 ()
!$omp declare variant (f18) match (construct={teams,parallel,do}) ! 16+8+4
!$omp declare variant (f19) match (construct={do},user={condition(score(25):1)}) ! 4+25
!$omp declare variant (f19) match (construct={do},user={condition(score(25):.true.)}) ! 4+25
!$omp declare variant (f20) match (implementation={atomic_default_mem_order(score(28):seq_cst)})
end subroutine
@ -110,7 +110,7 @@ contains
subroutine f29 ()
!$omp declare variant (f26) match (construct={parallel,do}) ! 2+1
!$omp declare variant (f27) match (construct={do},user={condition(1)}) ! 4
!$omp declare variant (f27) match (construct={do},user={condition(.true.)}) ! 4
!$omp declare variant (f28) match (implementation={atomic_default_mem_order(score(3):seq_cst)})
end subroutine

View file

@ -30,7 +30,7 @@ contains
!$omp declare variant (f01) match (device={isa("avx512f")}) ! 4 or 8
!$omp declare variant (f02) match (implementation={vendor(score(3):gnu)},device={kind(cpu)}) ! (1 or 2) + 3
!$omp declare variant (f03) match (user={condition(score(9):1)})
!$omp declare variant (f03) match (user={condition(score(9):.true.)})
!$omp declare variant (f04) match (implementation={vendor(score(6):gnu)},device={kind(host)}) ! (1 or 2) + 6
f05 = x
end function

View file

@ -15,7 +15,7 @@ contains
!$omp declare variant () ! { dg-error "" }
end subroutine
subroutine f5 ()
!$omp declare variant match(user={condition(0)}) ! { dg-error "expected '\\(' at .1." }
!$omp declare variant match(user={condition(.false.)}) ! { dg-error "expected '\\(' at .1." }
end subroutine
subroutine f6 ()
!$omp declare variant (f1) ! { dg-error "expected 'match' at .1." }
@ -66,7 +66,7 @@ contains
!$omp declare variant (f1) match(user={condition(f1)}) ! { dg-error "expected expression at .1." }
end subroutine
subroutine f22 ()
!$omp declare variant (f1) match(user={condition(1, 2, 3)}) ! { dg-error "expected '\\)' at .1." }
!$omp declare variant (f1) match(user={condition(.false., .true., .false.)}) ! { dg-error "expected '\\)' at .1." }
end subroutine
subroutine f23 ()
!$omp declare variant (f1) match(construct={master}) ! { dg-warning "unknown selector 'master' for context selector set 'construct'" }
@ -189,9 +189,9 @@ contains
!$omp declare variant (f1) match(implementation={atomic_default_mem_order("relaxed")}) ! { dg-error "expected identifier at .1." }
end subroutine
subroutine f77 ()
!$omp declare variant (f1) match(user={condition(score(f76):1)}) ! { dg-error ".score. argument must be constant integer expression at .1." }
!$omp declare variant (f1) match(user={condition(score(f76):.true.)}) ! { dg-error ".score. argument must be constant integer expression at .1." }
end subroutine
subroutine f78 ()
!$omp declare variant (f1) match(user={condition(score(-130):1)}) ! { dg-error ".score. argument must be non-negative" }
!$omp declare variant (f1) match(user={condition(score(-130):.true.)}) ! { dg-error ".score. argument must be non-negative" }
end subroutine
end module

View file

@ -0,0 +1,51 @@
! PR middle-end/113904
module m
implicit none (type, external)
logical, parameter :: parameter_true = .false.
logical :: false_flag = .false.
integer :: my_dev_num
contains
integer function variant1() result(res)
res = 1
end function
integer function variant2() result(res)
res = 2
end function
integer function variant3() result(res)
res = 3
end function
integer function variant4() result(res)
res = 4
end function
integer function variant5() result(res)
res = 4
end function
integer function variant6() result(res)
res = 4
end function
integer function foo() result(res)
! 'condition'
!$omp declare variant(variant1) match(user={condition(parameter_true)},construct={teams}) ! OK
! Below: OK since OpenMP 5.1 - but not yet supported: PR middle-end/113904
!$omp declare variant(variant2) match(user={condition(false_flag)},construct={parallel}) ! { dg-error "property must be a constant logical expression" }
!$omp declare variant(variant3) match(user={condition(1)},construct={target}) ! { dg-error "property must be a constant logical expression" }
! 'device_num'
!$omp declare variant(variant4) match(target_device={device_num(0)}) ! OK
!$omp declare variant(variant4) match(target_device={device_num(2)}) ! OK - assuming there are two non-host devices.
!$omp declare variant(variant5) match(target_device={device_num(-1)}) ! OK - omp_initial_device
!$omp declare variant(variant5) match(target_device={device_num(-4)}) ! OK - omp_invalid_device (will never match)
! OK - but not handled -> PR middle-end/113904
!$omp declare variant(variant5) match(target_device={device_num(my_device)}) ! { dg-error "property must be a constant integer expression" }
!$omp declare variant(variant5) match(target_device={device_num(-2)}) ! { dg-error "property must be a conforming device number" }
res = 99
end
end module m

View file

@ -10,10 +10,10 @@ contains
!$omp declare variant (f1) match(construct={parallel},construct={parallel}) ! { dg-error "selector set 'construct' specified more than once" }
end subroutine
subroutine f30 ()
!$omp declare variant (f1) match(user={condition(0)},construct={target},user={condition(0)}) ! { dg-error "selector set 'user' specified more than once" }
!$omp declare variant (f1) match(user={condition(.false.)},construct={target},user={condition(.false.)}) ! { dg-error "selector set 'user' specified more than once" }
end subroutine
subroutine f31 ()
!$omp declare variant (f1) match(user={condition(0)},user={condition(1)}) ! { dg-error "selector set 'user' specified more than once" }
!$omp declare variant (f1) match(user={condition(.false.)},user={condition(.true.)}) ! { dg-error "selector set 'user' specified more than once" }
end subroutine
subroutine f37 ()
!$omp declare variant (f1) match(device={kind(unknown)}) ! { dg-warning "unknown property 'unknown' of 'kind' selector" }

View file

@ -210,13 +210,13 @@ contains
!$omp& vendor(score(22):gnu),unified_address,extension(score(22):foobar)}) ! { dg-warning "unknown property 'foobar' of 'extension' selector" "" { target *-*-* } .-1 }
end subroutine
subroutine f72 ()
!$omp declare variant (f13) match (user={condition(0)})
!$omp declare variant (f13) match (user={condition(.false.)})
end subroutine
subroutine f73 ()
!$omp declare variant (f13) match (user={condition(272-272*1)})
!$omp declare variant (f13) match (user={condition(.true..and..not..true.)})
end subroutine
subroutine f74 ()
!$omp declare variant (f13) match (user={condition(score(25):1)})
!$omp declare variant (f13) match (user={condition(score(25):.true.)})
end subroutine
subroutine f75 ()
!$omp declare variant (f13) match (device={kind(any,"any")})
@ -231,7 +231,7 @@ contains
!$omp declare variant (f13) match (implementation={vendor(nvidia)})
end subroutine
subroutine f79 ()
!$omp declare variant (f13) match (user={condition(score(0):0)})
!$omp declare variant (f13) match (user={condition(score(0):.false.)})
end subroutine
end module

View file

@ -44,10 +44,10 @@ contains
end function
end interface
!$omp declare variant (f1) match (user={condition(1)})
!$omp declare variant (f2) match (user={condition(score(1):1)})
!$omp declare variant (f3) match (user={condition(score(3):1)})
!$omp declare variant (f4) match (user={condition(score(2):1)})
!$omp declare variant (f1) match (user={condition(.true.)})
!$omp declare variant (f2) match (user={condition(score(1):.true.)})
!$omp declare variant (f3) match (user={condition(score(3):.true.)})
!$omp declare variant (f4) match (user={condition(score(2):.true.)})
!$omp declare variant (f5) match (implementation={vendor(gnu)})
f6 = z + x + y

View file

@ -24,7 +24,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f1) match (user={condition(0)},construct={parallel})
!$omp declare variant (f1) match (user={condition(.false.)},construct={parallel})
f3 = 0.0
end function
@ -33,7 +33,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f1) match (construct={parallel},user={condition(score(1):1)})
!$omp declare variant (f1) match (construct={parallel},user={condition(score(1):.true.)})
f4 = 0.0
end function
@ -50,7 +50,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f5) match (user={condition(0)}) ! { dg-error "'f5' used as a variant with incompatible 'construct' selector sets" }
!$omp declare variant (f5) match (user={condition(.false.)}) ! { dg-error "'f5' used as a variant with incompatible 'construct' selector sets" }
f6 = 0.0
end function
@ -59,7 +59,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f5) match (construct={parallel},user={condition(score(1):1)})
!$omp declare variant (f5) match (construct={parallel},user={condition(score(1):.true.)})
f7 = 0.0
end function
@ -76,7 +76,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f8) match (user={condition(0)},construct={do}) ! { dg-error "'f8' used as a variant with incompatible 'construct' selector sets" }
!$omp declare variant (f8) match (user={condition(.false.)},construct={do}) ! { dg-error "'f8' used as a variant with incompatible 'construct' selector sets" }
f9 = 0.0
end function
@ -85,7 +85,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f8) match (user={condition(1)})
!$omp declare variant (f8) match (user={condition(.true.)})
f10 = 0.0
end function
@ -111,7 +111,7 @@ contains
integer, intent(in) :: x
integer (kind = 8), intent(in) :: y
real :: z
!$omp declare variant (f11) match (user={condition(score(1):1)},construct={target,teams,parallel,do}) ! { dg-error "'f11' used as a variant with incompatible 'construct' selector sets" }
!$omp declare variant (f11) match (user={condition(score(1):.true.)},construct={target,teams,parallel,do}) ! { dg-error "'f11' used as a variant with incompatible 'construct' selector sets" }
f13 = 0.0
end function

View file

@ -23,7 +23,7 @@ contains
end subroutine
subroutine f06 ()
!$omp declare variant (f05) match (user={condition(1)},implementation={atomic_default_mem_order(relaxed)})
!$omp declare variant (f05) match (user={condition(.true.)},implementation={atomic_default_mem_order(relaxed)})
end subroutine
subroutine f07 ()