2023-02-01 21:49:36 +08:00
! { dg-do compile }
subroutine test ( )
use iso_c_binding , only : c_intptr_t
implicit none
integer , parameter :: omp_allocator_handle_kind = 1 !! <<<
integer ( kind = omp_allocator_handle_kind ) , &
parameter :: omp_high_bw_mem_alloc = 4
integer :: q , x , y , z
integer , parameter :: cnst ( 2 ) = [ 64 , 101 ]
!$omp parallel allocate( omp_high_bw_mem_alloc : x) firstprivate(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind" }
!$omp end parallel
!$omp parallel allocate( allocator (omp_high_bw_mem_alloc) : x) firstprivate(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind" }
!$omp end parallel
Fortran/OpenMP: Add parsing support for allocators/allocate directives
gcc/fortran/ChangeLog:
* dump-parse-tree.cc (show_omp_namelist): Update allocator, fix
align dump.
(show_omp_node, show_code_node): Handle EXEC_OMP_ALLOCATE.
* gfortran.h (enum gfc_statement): Add ST_OMP_ALLOCATE and ..._EXEC.
(enum gfc_exec_op): Add EXEC_OMP_ALLOCATE.
(struct gfc_omp_namelist): Add 'allocator' to 'u2' union.
(struct gfc_namespace): Add omp_allocate.
(gfc_resolve_omp_allocate): New.
* match.cc (gfc_free_omp_namelist): Free 'u2.allocator'.
* match.h (gfc_match_omp_allocate, gfc_match_omp_allocators): New.
* openmp.cc (gfc_omp_directives): Uncomment allocate/allocators.
(gfc_match_omp_variable_list): Add bool arg for
rejecting listening common-block vars separately.
(gfc_match_omp_clauses): Update for u2.allocators.
(OMP_ALLOCATORS_CLAUSES, gfc_match_omp_allocate,
gfc_match_omp_allocators, is_predefined_allocator,
gfc_resolve_omp_allocate): New.
(resolve_omp_clauses): Update 'allocate' clause checks.
(omp_code_to_statement, gfc_resolve_omp_directive): Handle
OMP ALLOCATE/ALLOCATORS.
* parse.cc (in_exec_part): New global var.
(check_omp_allocate_stmt, parse_openmp_allocate_block): New.
(decode_omp_directive, case_exec_markers, case_omp_decl,
gfc_ascii_statement, parse_omp_structured_block): Handle
OMP allocate/allocators.
(verify_st_order, parse_executable): Set in_exec_part.
* resolve.cc (gfc_resolve_blocks, resolve_codes): Handle
allocate/allocators.
* st.cc (gfc_free_statement): Likewise.
* trans.cc (trans_code): Likewise.
* trans-openmp.cc (gfc_trans_omp_directive): Likewise.
(gfc_trans_omp_clauses, gfc_split_omp_clauses): Update for
u2.allocator, fix for u.align.
libgomp/ChangeLog:
* testsuite/libgomp.fortran/allocate-4.f90: Update dg-error.
gcc/testsuite/ChangeLog:
* gfortran.dg/gomp/allocate-2.f90: Update dg-error.
* gfortran.dg/gomp/allocate-4.f90: New test.
* gfortran.dg/gomp/allocate-5.f90: New test.
* gfortran.dg/gomp/allocate-6.f90: New test.
* gfortran.dg/gomp/allocate-7.f90: New test.
* gfortran.dg/gomp/allocators-1.f90: New test.
* gfortran.dg/gomp/allocators-2.f90: New test.
2023-05-27 02:39:33 +08:00
!$omp parallel allocate( align (q) : x) firstprivate(x) ! { dg-error "32:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
2023-02-01 21:49:36 +08:00
!$omp end parallel
!$omp parallel allocate( align (32) : x) firstprivate(x) ! OK
!$omp end parallel
Fortran/OpenMP: Add parsing support for allocators/allocate directives
gcc/fortran/ChangeLog:
* dump-parse-tree.cc (show_omp_namelist): Update allocator, fix
align dump.
(show_omp_node, show_code_node): Handle EXEC_OMP_ALLOCATE.
* gfortran.h (enum gfc_statement): Add ST_OMP_ALLOCATE and ..._EXEC.
(enum gfc_exec_op): Add EXEC_OMP_ALLOCATE.
(struct gfc_omp_namelist): Add 'allocator' to 'u2' union.
(struct gfc_namespace): Add omp_allocate.
(gfc_resolve_omp_allocate): New.
* match.cc (gfc_free_omp_namelist): Free 'u2.allocator'.
* match.h (gfc_match_omp_allocate, gfc_match_omp_allocators): New.
* openmp.cc (gfc_omp_directives): Uncomment allocate/allocators.
(gfc_match_omp_variable_list): Add bool arg for
rejecting listening common-block vars separately.
(gfc_match_omp_clauses): Update for u2.allocators.
(OMP_ALLOCATORS_CLAUSES, gfc_match_omp_allocate,
gfc_match_omp_allocators, is_predefined_allocator,
gfc_resolve_omp_allocate): New.
(resolve_omp_clauses): Update 'allocate' clause checks.
(omp_code_to_statement, gfc_resolve_omp_directive): Handle
OMP ALLOCATE/ALLOCATORS.
* parse.cc (in_exec_part): New global var.
(check_omp_allocate_stmt, parse_openmp_allocate_block): New.
(decode_omp_directive, case_exec_markers, case_omp_decl,
gfc_ascii_statement, parse_omp_structured_block): Handle
OMP allocate/allocators.
(verify_st_order, parse_executable): Set in_exec_part.
* resolve.cc (gfc_resolve_blocks, resolve_codes): Handle
allocate/allocators.
* st.cc (gfc_free_statement): Likewise.
* trans.cc (trans_code): Likewise.
* trans-openmp.cc (gfc_trans_omp_directive): Likewise.
(gfc_trans_omp_clauses, gfc_split_omp_clauses): Update for
u2.allocator, fix for u.align.
libgomp/ChangeLog:
* testsuite/libgomp.fortran/allocate-4.f90: Update dg-error.
gcc/testsuite/ChangeLog:
* gfortran.dg/gomp/allocate-2.f90: Update dg-error.
* gfortran.dg/gomp/allocate-4.f90: New test.
* gfortran.dg/gomp/allocate-5.f90: New test.
* gfortran.dg/gomp/allocate-6.f90: New test.
* gfortran.dg/gomp/allocate-7.f90: New test.
* gfortran.dg/gomp/allocators-1.f90: New test.
* gfortran.dg/gomp/allocators-2.f90: New test.
2023-05-27 02:39:33 +08:00
!$omp parallel allocate( align(q) : x) firstprivate(x) ! { dg-error "31:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
2023-02-01 21:49:36 +08:00
!$omp end parallel
!$omp parallel allocate( align(cnst(1)) : x ) firstprivate(x) ! OK
!$omp end parallel
Fortran/OpenMP: Add parsing support for allocators/allocate directives
gcc/fortran/ChangeLog:
* dump-parse-tree.cc (show_omp_namelist): Update allocator, fix
align dump.
(show_omp_node, show_code_node): Handle EXEC_OMP_ALLOCATE.
* gfortran.h (enum gfc_statement): Add ST_OMP_ALLOCATE and ..._EXEC.
(enum gfc_exec_op): Add EXEC_OMP_ALLOCATE.
(struct gfc_omp_namelist): Add 'allocator' to 'u2' union.
(struct gfc_namespace): Add omp_allocate.
(gfc_resolve_omp_allocate): New.
* match.cc (gfc_free_omp_namelist): Free 'u2.allocator'.
* match.h (gfc_match_omp_allocate, gfc_match_omp_allocators): New.
* openmp.cc (gfc_omp_directives): Uncomment allocate/allocators.
(gfc_match_omp_variable_list): Add bool arg for
rejecting listening common-block vars separately.
(gfc_match_omp_clauses): Update for u2.allocators.
(OMP_ALLOCATORS_CLAUSES, gfc_match_omp_allocate,
gfc_match_omp_allocators, is_predefined_allocator,
gfc_resolve_omp_allocate): New.
(resolve_omp_clauses): Update 'allocate' clause checks.
(omp_code_to_statement, gfc_resolve_omp_directive): Handle
OMP ALLOCATE/ALLOCATORS.
* parse.cc (in_exec_part): New global var.
(check_omp_allocate_stmt, parse_openmp_allocate_block): New.
(decode_omp_directive, case_exec_markers, case_omp_decl,
gfc_ascii_statement, parse_omp_structured_block): Handle
OMP allocate/allocators.
(verify_st_order, parse_executable): Set in_exec_part.
* resolve.cc (gfc_resolve_blocks, resolve_codes): Handle
allocate/allocators.
* st.cc (gfc_free_statement): Likewise.
* trans.cc (trans_code): Likewise.
* trans-openmp.cc (gfc_trans_omp_directive): Likewise.
(gfc_trans_omp_clauses, gfc_split_omp_clauses): Update for
u2.allocator, fix for u.align.
libgomp/ChangeLog:
* testsuite/libgomp.fortran/allocate-4.f90: Update dg-error.
gcc/testsuite/ChangeLog:
* gfortran.dg/gomp/allocate-2.f90: Update dg-error.
* gfortran.dg/gomp/allocate-4.f90: New test.
* gfortran.dg/gomp/allocate-5.f90: New test.
* gfortran.dg/gomp/allocate-6.f90: New test.
* gfortran.dg/gomp/allocate-7.f90: New test.
* gfortran.dg/gomp/allocators-1.f90: New test.
* gfortran.dg/gomp/allocators-2.f90: New test.
2023-05-27 02:39:33 +08:00
!$omp parallel allocate( align(cnst(2)) : x) firstprivate(x) ! { dg-error "31:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
2023-02-01 21:49:36 +08:00
!$omp end parallel
Fortran/OpenMP: Add parsing support for allocators/allocate directives
gcc/fortran/ChangeLog:
* dump-parse-tree.cc (show_omp_namelist): Update allocator, fix
align dump.
(show_omp_node, show_code_node): Handle EXEC_OMP_ALLOCATE.
* gfortran.h (enum gfc_statement): Add ST_OMP_ALLOCATE and ..._EXEC.
(enum gfc_exec_op): Add EXEC_OMP_ALLOCATE.
(struct gfc_omp_namelist): Add 'allocator' to 'u2' union.
(struct gfc_namespace): Add omp_allocate.
(gfc_resolve_omp_allocate): New.
* match.cc (gfc_free_omp_namelist): Free 'u2.allocator'.
* match.h (gfc_match_omp_allocate, gfc_match_omp_allocators): New.
* openmp.cc (gfc_omp_directives): Uncomment allocate/allocators.
(gfc_match_omp_variable_list): Add bool arg for
rejecting listening common-block vars separately.
(gfc_match_omp_clauses): Update for u2.allocators.
(OMP_ALLOCATORS_CLAUSES, gfc_match_omp_allocate,
gfc_match_omp_allocators, is_predefined_allocator,
gfc_resolve_omp_allocate): New.
(resolve_omp_clauses): Update 'allocate' clause checks.
(omp_code_to_statement, gfc_resolve_omp_directive): Handle
OMP ALLOCATE/ALLOCATORS.
* parse.cc (in_exec_part): New global var.
(check_omp_allocate_stmt, parse_openmp_allocate_block): New.
(decode_omp_directive, case_exec_markers, case_omp_decl,
gfc_ascii_statement, parse_omp_structured_block): Handle
OMP allocate/allocators.
(verify_st_order, parse_executable): Set in_exec_part.
* resolve.cc (gfc_resolve_blocks, resolve_codes): Handle
allocate/allocators.
* st.cc (gfc_free_statement): Likewise.
* trans.cc (trans_code): Likewise.
* trans-openmp.cc (gfc_trans_omp_directive): Likewise.
(gfc_trans_omp_clauses, gfc_split_omp_clauses): Update for
u2.allocator, fix for u.align.
libgomp/ChangeLog:
* testsuite/libgomp.fortran/allocate-4.f90: Update dg-error.
gcc/testsuite/ChangeLog:
* gfortran.dg/gomp/allocate-2.f90: Update dg-error.
* gfortran.dg/gomp/allocate-4.f90: New test.
* gfortran.dg/gomp/allocate-5.f90: New test.
* gfortran.dg/gomp/allocate-6.f90: New test.
* gfortran.dg/gomp/allocate-7.f90: New test.
* gfortran.dg/gomp/allocators-1.f90: New test.
* gfortran.dg/gomp/allocators-2.f90: New test.
2023-05-27 02:39:33 +08:00
!$omp parallel allocate( align( 31) :x) firstprivate(x) ! { dg-error "32:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
2023-02-01 21:49:36 +08:00
!$omp end parallel
Fortran/OpenMP: Add parsing support for allocators/allocate directives
gcc/fortran/ChangeLog:
* dump-parse-tree.cc (show_omp_namelist): Update allocator, fix
align dump.
(show_omp_node, show_code_node): Handle EXEC_OMP_ALLOCATE.
* gfortran.h (enum gfc_statement): Add ST_OMP_ALLOCATE and ..._EXEC.
(enum gfc_exec_op): Add EXEC_OMP_ALLOCATE.
(struct gfc_omp_namelist): Add 'allocator' to 'u2' union.
(struct gfc_namespace): Add omp_allocate.
(gfc_resolve_omp_allocate): New.
* match.cc (gfc_free_omp_namelist): Free 'u2.allocator'.
* match.h (gfc_match_omp_allocate, gfc_match_omp_allocators): New.
* openmp.cc (gfc_omp_directives): Uncomment allocate/allocators.
(gfc_match_omp_variable_list): Add bool arg for
rejecting listening common-block vars separately.
(gfc_match_omp_clauses): Update for u2.allocators.
(OMP_ALLOCATORS_CLAUSES, gfc_match_omp_allocate,
gfc_match_omp_allocators, is_predefined_allocator,
gfc_resolve_omp_allocate): New.
(resolve_omp_clauses): Update 'allocate' clause checks.
(omp_code_to_statement, gfc_resolve_omp_directive): Handle
OMP ALLOCATE/ALLOCATORS.
* parse.cc (in_exec_part): New global var.
(check_omp_allocate_stmt, parse_openmp_allocate_block): New.
(decode_omp_directive, case_exec_markers, case_omp_decl,
gfc_ascii_statement, parse_omp_structured_block): Handle
OMP allocate/allocators.
(verify_st_order, parse_executable): Set in_exec_part.
* resolve.cc (gfc_resolve_blocks, resolve_codes): Handle
allocate/allocators.
* st.cc (gfc_free_statement): Likewise.
* trans.cc (trans_code): Likewise.
* trans-openmp.cc (gfc_trans_omp_directive): Likewise.
(gfc_trans_omp_clauses, gfc_split_omp_clauses): Update for
u2.allocator, fix for u.align.
libgomp/ChangeLog:
* testsuite/libgomp.fortran/allocate-4.f90: Update dg-error.
gcc/testsuite/ChangeLog:
* gfortran.dg/gomp/allocate-2.f90: Update dg-error.
* gfortran.dg/gomp/allocate-4.f90: New test.
* gfortran.dg/gomp/allocate-5.f90: New test.
* gfortran.dg/gomp/allocate-6.f90: New test.
* gfortran.dg/gomp/allocate-7.f90: New test.
* gfortran.dg/gomp/allocators-1.f90: New test.
* gfortran.dg/gomp/allocators-2.f90: New test.
2023-05-27 02:39:33 +08:00
!$omp parallel allocate( align (32.0): x) firstprivate(x) ! { dg-error "32:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
2023-02-01 21:49:36 +08:00
!$omp end parallel
Fortran/OpenMP: Add parsing support for allocators/allocate directives
gcc/fortran/ChangeLog:
* dump-parse-tree.cc (show_omp_namelist): Update allocator, fix
align dump.
(show_omp_node, show_code_node): Handle EXEC_OMP_ALLOCATE.
* gfortran.h (enum gfc_statement): Add ST_OMP_ALLOCATE and ..._EXEC.
(enum gfc_exec_op): Add EXEC_OMP_ALLOCATE.
(struct gfc_omp_namelist): Add 'allocator' to 'u2' union.
(struct gfc_namespace): Add omp_allocate.
(gfc_resolve_omp_allocate): New.
* match.cc (gfc_free_omp_namelist): Free 'u2.allocator'.
* match.h (gfc_match_omp_allocate, gfc_match_omp_allocators): New.
* openmp.cc (gfc_omp_directives): Uncomment allocate/allocators.
(gfc_match_omp_variable_list): Add bool arg for
rejecting listening common-block vars separately.
(gfc_match_omp_clauses): Update for u2.allocators.
(OMP_ALLOCATORS_CLAUSES, gfc_match_omp_allocate,
gfc_match_omp_allocators, is_predefined_allocator,
gfc_resolve_omp_allocate): New.
(resolve_omp_clauses): Update 'allocate' clause checks.
(omp_code_to_statement, gfc_resolve_omp_directive): Handle
OMP ALLOCATE/ALLOCATORS.
* parse.cc (in_exec_part): New global var.
(check_omp_allocate_stmt, parse_openmp_allocate_block): New.
(decode_omp_directive, case_exec_markers, case_omp_decl,
gfc_ascii_statement, parse_omp_structured_block): Handle
OMP allocate/allocators.
(verify_st_order, parse_executable): Set in_exec_part.
* resolve.cc (gfc_resolve_blocks, resolve_codes): Handle
allocate/allocators.
* st.cc (gfc_free_statement): Likewise.
* trans.cc (trans_code): Likewise.
* trans-openmp.cc (gfc_trans_omp_directive): Likewise.
(gfc_trans_omp_clauses, gfc_split_omp_clauses): Update for
u2.allocator, fix for u.align.
libgomp/ChangeLog:
* testsuite/libgomp.fortran/allocate-4.f90: Update dg-error.
gcc/testsuite/ChangeLog:
* gfortran.dg/gomp/allocate-2.f90: Update dg-error.
* gfortran.dg/gomp/allocate-4.f90: New test.
* gfortran.dg/gomp/allocate-5.f90: New test.
* gfortran.dg/gomp/allocate-6.f90: New test.
* gfortran.dg/gomp/allocate-7.f90: New test.
* gfortran.dg/gomp/allocators-1.f90: New test.
* gfortran.dg/gomp/allocators-2.f90: New test.
2023-05-27 02:39:33 +08:00
!$omp parallel allocate( align(cnst ) : x ) firstprivate(x) ! { dg-error "31:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
2023-02-01 21:49:36 +08:00
!$omp end parallel
end