
The 'uses_allocators' clause to the 'target' construct accepts predefined allocators and can also be used to define a new allocator for a target region. As predefined allocators in GCC do not require special handling, those can and are ignored after parsing, such that this feature now works. On the other hand, defining a new allocator will fail for now with a 'sorry, unimplemented'. Note that both the OpenMP 5.0/5.1 and 5.2 syntax for uses_allocators is supported by this commit. 2023-07-17 Tobias Burnus <tobias@codesoucery.com> Chung-Lin Tang <cltang@codesourcery.com> gcc/fortran/ChangeLog: * dump-parse-tree.cc (show_omp_namelist, show_omp_clauses): Dump uses_allocators clause. * gfortran.h (gfc_free_omp_namelist): Add memspace_sym to u union and traits_sym to u2 union. (OMP_LIST_USES_ALLOCATORS): New enum value. (gfc_free_omp_namelist): Add 'bool free_mem_traits_space' arg. * match.cc (gfc_free_omp_namelist): Likewise. * openmp.cc (gfc_free_omp_clauses, gfc_match_omp_variable_list, gfc_match_omp_to_link, gfc_match_omp_doacross_sink, gfc_match_omp_clause_reduction, gfc_match_omp_allocate, gfc_match_omp_flush): Update call. (gfc_match_omp_clauses): Likewise. Parse uses_allocators clause. (gfc_match_omp_clause_uses_allocators): New. (enum omp_mask2): Add new OMP_CLAUSE_USES_ALLOCATORS. (OMP_TARGET_CLAUSES): Accept it. (resolve_omp_clauses): Resolve uses_allocators clause * st.cc (gfc_free_statement): Update gfc_free_omp_namelist call. * trans-openmp.cc (gfc_trans_omp_clauses): Handle OMP_LIST_USES_ALLOCATORS; fail with sorry unless predefined allocator. (gfc_split_omp_clauses): Handle uses_allocators. libgomp/ChangeLog: * testsuite/libgomp.fortran/uses_allocators_1.f90: New test. * testsuite/libgomp.fortran/uses_allocators_2.f90: New test. Co-authored-by: Chung-Lin Tang <cltang@codesourcery.com>
99 lines
4.2 KiB
Fortran
99 lines
4.2 KiB
Fortran
! { dg-do compile }
|
|
|
|
! Minimal test for valid code:
|
|
! - predefined allocators do not need any special treatment in uses_allocators
|
|
! (as 'requires dynamic_allocators' is the default).
|
|
!
|
|
! - Non-predefined allocators are currently rejected ('sorry)'
|
|
|
|
subroutine test
|
|
use omp_lib
|
|
implicit none
|
|
|
|
!$omp target uses_allocators ( omp_default_mem_alloc , omp_large_cap_mem_alloc, &
|
|
!$omp& omp_const_mem_alloc,omp_high_bw_mem_alloc, &
|
|
!$omp& omp_low_lat_mem_alloc ,omp_cgroup_mem_alloc , &
|
|
!$omp& omp_pteam_mem_alloc, omp_thread_mem_alloc )
|
|
block; end block
|
|
|
|
!$omp target parallel uses_allocators ( omp_default_mem_alloc , omp_large_cap_mem_alloc, &
|
|
!$omp& omp_const_mem_alloc,omp_high_bw_mem_alloc, &
|
|
!$omp& omp_low_lat_mem_alloc ,omp_cgroup_mem_alloc , &
|
|
!$omp& omp_pteam_mem_alloc, omp_thread_mem_alloc )
|
|
block; end block
|
|
end
|
|
|
|
subroutine non_predef
|
|
use omp_lib
|
|
implicit none
|
|
|
|
type(omp_alloctrait), parameter :: trait(0) = [omp_alloctrait :: ]
|
|
type(omp_alloctrait), parameter :: trait2(*) &
|
|
= [omp_alloctrait (omp_atk_alignment, 16), &
|
|
omp_alloctrait (omp_atk_sync_hint, omp_atv_default), &
|
|
omp_alloctrait (omp_atk_access, omp_atv_default)]
|
|
|
|
integer(kind=omp_allocator_handle_kind) :: a1, a2, a3
|
|
|
|
!$omp target uses_allocators(omp_default_mem_alloc, a1(trait), a2(trait2)) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
|
|
!$omp target parallel uses_allocators(omp_default_mem_alloc, a1(trait), a2(trait2)) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
|
|
|
|
!$omp target uses_allocators(traits(trait):a1) &
|
|
!$omp& uses_allocators ( memspace ( omp_low_lat_mem_space ) , traits ( trait2 ) : a2 , a3) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
|
|
!$omp target parallel uses_allocators(traits(trait):a1) &
|
|
!$omp& uses_allocators ( memspace ( omp_low_lat_mem_space ) , traits ( trait2 ) : a2 , a3) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
|
|
!$omp target uses_allocators ( traits(trait2) , memspace ( omp_low_lat_mem_space ) : a2 , a3) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
end subroutine
|
|
|
|
subroutine trait_present
|
|
use omp_lib
|
|
implicit none
|
|
|
|
type(omp_alloctrait), parameter :: trait1(0) = [omp_alloctrait :: ]
|
|
integer(kind=omp_allocator_handle_kind) :: a1
|
|
|
|
! Invalid in OpenMP 5.0 / 5.1, but valid since 5.2 the same as omp_default_mem_space + emptry traits array
|
|
!$omp target uses_allocators ( a1 ) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
end
|
|
|
|
subroutine odd_names
|
|
use omp_lib
|
|
implicit none
|
|
|
|
type(omp_alloctrait), parameter :: trait1(0) = [omp_alloctrait :: ]
|
|
|
|
! oddly named allocators:
|
|
integer(kind=omp_allocator_handle_kind) :: traits
|
|
integer(kind=omp_allocator_handle_kind) :: memspace
|
|
|
|
!$omp target uses_allocators ( traits(trait1), memspace(trait1) ) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
|
|
!$omp target uses_allocators ( traits(trait1), memspace(omp_low_lat_mem_space) : traits) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
|
|
!$omp target uses_allocators ( memspace(omp_low_lat_mem_space), traits(trait1) : memspace) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
end
|
|
|
|
subroutine more_checks
|
|
use omp_lib
|
|
implicit none
|
|
|
|
integer(kind=kind(omp_low_lat_mem_space)) :: my_memspace
|
|
integer(kind=omp_allocator_handle_kind) :: a1, a2(4)
|
|
integer(kind=1) :: a3
|
|
|
|
!$omp target uses_allocators(memspace (omp_low_lat_mem_space) : a1 ) ! { dg-message "sorry, unimplemented: 'uses_allocators' clause with traits and memory spaces" }
|
|
block; end block
|
|
end
|