else if (gfc_match_char ('*') == MATCH_YES)
rop = OMP_REDUCTION_TIMES;
else if (gfc_match_char ('-') == MATCH_YES)
- rop = OMP_REDUCTION_MINUS;
+ {
+ gfc_warning (OPT_Wdeprecated_openmp, "%<-%> operator at %C "
+ "for reductions deprecated in OpenMP 5.2");
+ rop = OMP_REDUCTION_MINUS;
+ }
else if (gfc_match (".and.") == MATCH_YES)
rop = OMP_REDUCTION_AND;
else if (gfc_match (".or.") == MATCH_YES)
if (gfc_match ("%S ", &p->sym) != MATCH_YES)
goto error;
if (!has_modifiers)
- gfc_match ("( %S ) ", &p->u2.traits_sym);
+ {
+ if (gfc_match ("( %S ) ", &p->u2.traits_sym) == MATCH_YES)
+ gfc_warning (OPT_Wdeprecated_openmp, "The specification of "
+ "arguments to %<uses_allocators%> at %L where each item is of "
+ "the form %<allocator(traits)%> is deprecated since OpenMP 5.2",
+ &p->where);
+ }
else if (gfc_peek_ascii_char () == '(')
{
gfc_error ("Unexpected %<(%> at %C");
"at %C");
goto error;
}
+ if (is_depend)
+ gfc_warning (OPT_Wdeprecated_openmp, "%<source%> "
+ "modifier with %<depend%> clause at %L deprecated "
+ "since OpenMP 5.2, use with %<doacross%>", &old_loc);
c->doacross_source = true;
c->depend_source = is_depend;
continue;
"at %C");
goto error;
}
+ if (is_depend)
+ gfc_warning (OPT_Wdeprecated_openmp, "%<sink%> "
+ "modifier with %<depend%> clause at %L "
+ "deprecated since OpenMP 5.2, use with %<doacross%>",
+ &old_loc);
m = gfc_match_omp_doacross_sink (&c->lists[OMP_LIST_DEPEND],
is_depend);
if (m == MATCH_YES)
bool old_linear_modifier = false;
gfc_omp_linear_op linear_op = OMP_LINEAR_DEFAULT;
gfc_expr *step = NULL;
+ locus saved_loc = gfc_current_locus;
if (gfc_match_omp_variable_list (" ref (",
&c->lists[OMP_LIST_LINEAR],
gfc_current_locus = old_loc;
break;
}
+ if (old_linear_modifier)
+ gfc_warning (OPT_Wdeprecated_openmp,
+ "Specification of the list items as arguments to the "
+ "modifiers at %L is deprecated since OpenMP 5.2",
+ &saved_loc);
if (linear_op != OMP_LINEAR_DEFAULT)
{
if (gfc_match (" :") == MATCH_YES)
}
else
break;
- gfc_match (", ");
+ if (gfc_match (", ") != MATCH_YES)
+ gfc_warning (OPT_Wdeprecated_openmp,
+ "The specification of modifiers without comma "
+ "separators for the %<map%> clause at %C has "
+ "been deprecated since OpenMP 5.2");
}
gfc_omp_map_op map_op = OMP_MAP_TOFROM;
if (m == MATCH_ERROR)
goto error;
if (m == MATCH_YES)
- continue;
+ {
+ gfc_warning (OPT_Wdeprecated_openmp, "%<to%> clause with "
+ "%<declare target%> at %L deprecated since OpenMP 5.2, "
+ "use %<enter%>", &old_loc);
+ continue;
+ }
}
else if ((mask & OMP_CLAUSE_TO)
&& gfc_match_motion_var_list ("to (", &c->lists[OMP_LIST_TO],
locus variant_locus = gfc_current_locus;
- if (gfc_match (" default ( ") == MATCH_YES)
- default_p = true;
- else if (gfc_match (" otherwise ( ") == MATCH_YES)
+ if (gfc_match ("default ( ") == MATCH_YES)
+ {
+ default_p = true;
+ gfc_warning (OPT_Wdeprecated_openmp,
+ "%<default%> clause with metadirective at %L "
+ "deprecated since OpenMP 5.2", &variant_locus);
+ }
+ else if (gfc_match ("otherwise ( ") == MATCH_YES)
default_p = true;
- else if (gfc_match (" when ( ") != MATCH_YES)
+ else if (gfc_match ("when ( ") != MATCH_YES)
{
gfc_error ("expected %<when%>, %<otherwise%>, or %<default%> at %C");
gfc_current_locus = old_loc;
return MATCH_ERROR;
}
-
if (default_p && default_seen)
{
gfc_error ("too many %<otherwise%> or %<default%> clauses "
&& code->block->next
&& code->block->next->op == EXEC_ALLOCATE)
{
+ if (code->op == EXEC_OMP_ALLOCATE)
+ gfc_warning (OPT_Wdeprecated_openmp,
+ "The use of one or more %<allocate%> directives with "
+ "an associated %<allocate%> statement at %L is "
+ "deprecated since OpenMP 5.2, use an %<allocators%> "
+ "directive", &code->loc);
gfc_alloc *a;
gfc_omp_namelist *n_null = NULL;
bool missing_allocator = false;
n->sym->name, &n->where);
for (a = code->block->next->ext.alloc.list; a; a = a->next)
if (a->expr->expr_type == EXPR_VARIABLE
- && a->expr->symtree->n.sym == n->sym)
+ && a->expr->symtree->n.sym == n->sym)
{
gfc_ref *ref;
for (ref = a->expr->ref; ref; ref = ref->next)
--- /dev/null
+! { dg-error ".* at \\(1\\) requires '-fopenmp-allocators'" "" { target *-*-* } 24 }
+! { dg-warning "All files that might deallocate such a variable must be compiled with '-fopenmp-allocators'" "" { target *-*-* } 24 }
+program test_deprecations
+ integer :: i
+ integer :: j
+ integer, allocatable :: a(:)
+ integer :: x(10)
+ integer :: y, z
+
+ ! { dg-warning "'to' clause with 'declare target' at \\(1\\) deprecated since OpenMP 5.2, use 'enter' \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 11 }
+ !$omp declare target to(i)
+ !$omp do ordered(1)
+ do i = 1,10
+ ! { dg-warning "'source' modifier with 'depend' clause at \\(1\\) deprecated since OpenMP 5.2, use with 'doacross' \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 15 }
+ !$omp ordered depend(source)
+ j = i
+ ! { dg-warning "'sink' modifier with 'depend' clause at \\(1\\) deprecated since OpenMP 5.2, use with 'doacross' \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 18 }
+ !$omp ordered depend(sink : i)
+ j = i
+ end do
+ !$omp end do
+
+ ! { dg-warning "The use of one or more 'allocate' directives with an associated 'allocate' statement at \\(1\\) is deprecated since OpenMP 5.2, use an 'allocators' directive \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 24 }
+ !$omp allocate(a)
+ allocate(a(100))
+ do i = 1,100
+ a(i) = i
+ end do
+ deallocate(a)
+
+
+ ! { dg-warning "The specification of modifiers without comma separators for the 'map' clause at \\(1\\) has been deprecated since OpenMP 5.2 \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 33 }
+ !$omp target map(close to: x)
+ x = 1
+ !$omp end target
+
+ z = 1
+ ! { dg-warning "'-' operator at \\(1\\) for reductions deprecated in OpenMP 5.2 \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 39 }
+ !$omp parallel do reduction(-:z)
+ do y = 1,10
+ z = z - y
+ end do
+
+end program
! { dg-additional-options "-fcoarray=single -fcray-pointer" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
use iso_c_binding
integer, parameter :: omp_allocator_handle_kind = c_intptr_t
!$omp allocate(z) ! { dg-error "18:Unexpected coarray 'z' in 'allocate' at .1." }
allocate(z(5)[*])
x = 5
-end
+end
integer function f() result(res)
integer :: x
integer, allocatable :: a, b, c[:], d
x = 5 ! executable stmt
- !$omp allocators allocate(align(16): a,b) allocate(align(32) : d)
+ !$omp allocators allocate(align(16): a,b) allocate(align(32) : d)
allocate(a,b,c[*],d) ! OK - Fortran allocator used for 'C'
end
+! { dg-additional-options "-Wno-deprecated-openmp" }
integer, pointer :: ptr
!$omp flush
allocate(ptr)
end
-! { dg-error "'!.OMP ALLOCATE' at .1. requires '-fopenmp-allocators'" "" { target *-*-* } 4 }
+! { dg-error "'!$OMP ALLOCATE' at .1. requires '-fopenmp-allocators'" "" { target *-*-* } 4 }
! { dg-warning "All files that might deallocate such a variable must be compiled with '-fopenmp-allocators'" "" { target *-*-* } 4 }
! { dg-note "This includes explicit DEALLOCATE, reallocation on intrinsic assignment, INTENT\\(OUT\\) for allocatable dummy arguments, and reallocation of allocatable components allocated with an OpenMP allocator" "" { target *-*-* } 0 }
! { dg-additional-options "-fopenmp-allocators" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
module my_omp_lib
use iso_c_binding, only: c_intptr_t
!use omp_lib
+! { dg-additional-options "-Wno-deprecated-openmp" }
module my_omp_lib
use iso_c_binding, only: c_intptr_t
!use omp_lib
! { dg-additional-options "-fmax-errors=1000" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
module my_omp_lib
use iso_c_binding, only: c_intptr_t
!use omp_lib
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine f
integer, allocatable :: A1, A2, B(:), C
!$omp declare target
! { dg-do compile }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
function f1 (a, b, c, d, e, f)
integer, value :: a, b, c
integer :: d, e, f, f1
! { dg-do compile }
! { dg-additional-options "-fdump-tree-gimple" }
-!
+! { dg-additional-options "-Wno-deprecated-openmp" }
! PR fortran/106566
!
! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare simd \\(linear\\(ref\\(0\\):4\\) simdlen\\(8\\)\\)\\)\\)" 2 "gimple" } }
! { dg-do compile }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module declare_target_1
!$omp declare target to (var_1, var_4) link (var_2, var_3) &
!$omp & link (var_5) to (var_6)
! { dg-do compile }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module declare_target_2
!$omp declare target to (a) link (a) ! { dg-error "mentioned multiple times in clauses of the same OMP DECLARE TARGET directive" }
!$omp declare target (b)
! { dg-do compile }
! { dg-additional-options "-fdump-tree-original" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine f1
!$omp declare target device_type (any) ! { dg-warning "OMP DECLARE TARGET directive at .1. with only DEVICE_TYPE or INDIRECT clauses is ignored" }
end subroutine
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine foo()
!$omp declare target to(foo) device_type(bar) ! { dg-error "Expected HOST, NOHOST or ANY" }
end
! { dg-do compile }
! { dg-options "-fopenmp" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
integer :: a
integer, parameter :: X = 1
! { dg-do compile }
! { dg-options "-fopenmp -fdump-tree-gimple" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
contains
subroutine sub1
! { dg-do compile }
! { dg-additional-options "-cpp -foffload=disable -fdump-tree-gimple" }
! { dg-additional-options "-mavx512bw" { target { i?86-*-* x86_64-*-* } } }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
#undef i386
program main
! { dg-do compile }
! { dg-additional-options "-fdump-tree-gimple" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
program main
!$omp requires atomic_default_mem_order(seq_cst)
!$omp declare target to (test3)
subroutine foo
integer :: n = 5, m = 7
- !$omp declare target to(n)
+ !$omp declare target to(n) ! { dg-warning "'to' clause with 'declare target' at \\(1\\) deprecated since OpenMP 5.2, use 'enter' \\\[-Wdeprecated-openmp\\\]" }
!$omp threadprivate (m)
end
program main
integer :: i, j
- !$omp declare target to(i)
+ !$omp declare target to(i) ! { dg-warning "'to' clause with 'declare target' at \\(1\\) deprecated since OpenMP 5.2, use 'enter' \\\[-Wdeprecated-openmp\\\]" }
!$omp threadprivate (j)
end
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine foo (x, y)
integer :: i, x, y
common /i/ i
! { dg-do compile }
! { dg-options "-fopenmp -fdump-tree-original" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
implicit none (type, external)
! { dg-do compile }
! { dg-options "-fopenmp" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m2
implicit none (type, external)
! { dg-do compile }
! { dg-options "-fopenmp" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
implicit none
! { dg-do compile }
! { dg-options "-fopenmp" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
implicit none
integer, parameter :: val = 1
! { dg-additional-options "-fdump-tree-omplower -fdump-tree-original" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine foo
implicit none
integer :: a, b, b1
! { dg-additional-options "-fdump-tree-original" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
implicit none
integer :: a, b, b1, b2, b3, b4, b5, b6
! { dg-additional-options "-fdump-tree-original" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
implicit none
integer :: a, b, close, always, to, present
+! { dg-additional-options "-Wno-deprecated-openmp" }
implicit none
integer :: a
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine f1 (a)
integer :: a(*)
integer i
! PR middle-end/83977
! { dg-do compile }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
integer function foo (a, b)
integer :: a, b
!$omp declare simd uniform(b) linear(ref(a):b)
! { dg-do compile }
! { dg-options "-fopenmp -fmax-errors=100" }
! { dg-require-effective-target tls }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine foo (ia1)
integer :: i1, i2, i3
integer, dimension (*) :: ia1
! { dg-do compile }
! { dg-options "-fopenmp" }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine foo
integer :: i
!$omp do schedule (nonmonotonic: static, 2)
! { dg-do compile }
! { dg-options "-O2 -fopenmp -fdump-tree-optimized" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_doacross_start \[^\n\r]*, (?:2147483648|-2147483648), 0, " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_end " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_doacross_post " 1 "optimized" } }
! { dg-do compile }
! { dg-options "-O2 -fopenmp -fdump-tree-optimized" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop(?:_ull)?_doacross_start \[^\n\r]*, (?:2147483649|-2147483647), 0, " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_end " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_doacross(?:_ull)?_post " 1 "optimized" } }
! { dg-do compile }
! { dg-options "-O2 -fopenmp -fdump-tree-optimized" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop(?:_ull)?_doacross_start \[^\n\r]*, (?:2147483650|-2147483646), 1, " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_end " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_doacross(?:_ull)?_post " 1 "optimized" } }
! { dg-do compile }
! { dg-options "-O2 -fopenmp -fdump-tree-optimized" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_doacross_start \[^\n\r]*, (?:2147483651|-2147483645), 1, " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_end " 1 "optimized" } }
! { dg-final { scan-tree-dump-times "__builtin_GOMP_doacross_post " 1 "optimized" } }
! { dg-additional-options "-fopenmp-allocators" }
! { dg-additional-options "-fdump-tree-omplower" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
program main
use iso_c_binding
use omp_lib
! { dg-additional-options "-fopenmp-allocators -fdump-tree-original" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
use omp_lib
use iso_c_binding, only: c_intptr_t
implicit none (type,external)
- integer(omp_allocator_handle_kind) :: handle
+ integer(omp_allocator_handle_kind) :: handle
integer(c_intptr_t) :: iptr
end module m
! { dg-additional-options "-fopenmp-allocators" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
implicit none (type, external)
type t
! { dg-additional-options "-fopenmp-allocators" }
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
implicit none
type t
! { dg-do run }
! { dg-additional-sources declare-target-2.f90 }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module declare_target_1_mod
integer :: var_x, var_y, var_z
!$omp declare target(var_x)
! file compiled together with declare-target-1.f90
! to verify inter-CU module handling of omp declare target.
! { dg-do compile { target { lp64 && { ! lp64 } } } }
-
subroutine foo
use declare_target_1_mod
! { dg-do run }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
contains
integer function foo ()
! { dg-do run }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module m
contains
integer function foo ()
--- /dev/null
+! { dg-do compile }
+! { dg-warning "The specification of arguments to 'uses_allocators' at \\(1\\) where each item is of the form 'allocator\\(traits\\)' is deprecated since OpenMP 5.2 \\\[-Wdeprecated-openmp\\\]" "" { target *-*-* } 11 }
+
+program test
+ use omp_lib
+ implicit none
+ integer(kind=omp_allocator_handle_kind) :: a1
+
+ type(omp_alloctrait), parameter :: trait(0) = [omp_alloctrait :: ]
+
+ !$omp target uses_allocators(omp_default_mem_alloc, a1(trait))
+ ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" "" { target *-*-* } .-1 }
+ block; end block
+end program
! { dg-do run }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
integer, parameter :: N = 256
integer, save :: a(N), b(N / 16, 8, 4), c(N / 32, 8, 8)
integer, save, volatile :: d, e
! { dg-do run }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
integer, parameter :: N = 256
integer, save :: a(N), b(N / 16, 8, 4), c(N / 32, 8, 8), g(N/16,8,6)
integer, save, volatile :: d, e
! { dg-do run }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
integer, parameter :: N = 256
integer, save :: a(N), b(N / 16, 8, 4), c(N / 32, 8, 8), g(N/16,8,6)
integer, save, volatile :: d, e
! { dg-do run }
-!
+! { dg-additional-options "-Wno-deprecated-openmp" }
! PR fortran/96668
module m
contains
real function foo (x, y)
real :: x, y
- !$omp declare simd linear (ref (x, y))
+ !$omp declare simd linear (ref (x, y)) ! { dg-warning "Specification of the list items as arguments to the modifiers at \\(1\\) is deprecated since OpenMP 5.2 \\\[-Wdeprecated-openmp\\\]" }
foo = x + y
end function
end
! { dg-options "-fno-inline" }
! { dg-additional-options "-msse2" { target sse2_runtime } }
! { dg-additional-options "-mavx" { target avx_runtime } }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
type p
integer :: i, j
end type
do i = 1, 1024
if (c(i).ne.(6 * i)) stop 1
end do
-contains
+contains
function foo (x, y)
type (p) :: x
integer :: y(4), foo
cnt = -1
!$omp parallel num_threads (3) private (n) reduction (.or.:v) &
-!$omp & reduction (-:i, ia, r, ra, d, da, c, ca)
+!$omp & reduction (-:i, ia, r, ra, d, da, c, ca) ! { dg-warning "'-' operator at \\(1\\) for reductions deprecated in OpenMP 5.2 \\\[-Wdeprecated-openmp\\\]" }
!$ if (i .ne. 0 .or. any (ia .ne. 0)) v = .true.
!$ if (r .ne. 0 .or. any (ra .ne. 0)) v = .true.
!$ if (d .ne. 0 .or. any (da .ne. 0)) v = .true.
! { dg-do run }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
module udr11
type dt
integer :: x = 0
! { dg-do compile }
+! { dg-additional-options "-Wno-deprecated-openmp" }
subroutine test
use omp_lib
! { dg-do compile }
-
+! { dg-additional-options "-Wno-deprecated-openmp" }
! Minimal test for valid code:
! - predefined allocators do not need any special treatment in uses_allocators
! (as 'requires dynamic_allocators' is the default).