gcc/libgomp/testsuite/libgomp.oacc-fortran/declare-3.f90
James Norris dc7a8b4b7a dump-parse-tree.c (show_namespace): Handle declares.
gcc/fortran/
	* dump-parse-tree.c (show_namespace): Handle declares.
	* gfortran.h (struct symbol_attribute): New fields.
	(enum gfc_omp_map_map): Add OMP_MAP_DEVICE_RESIDENT and OMP_MAP_LINK.
	(OMP_LIST_LINK): New enum.
	(struct gfc_oacc_declare): New structure.
	(gfc_get_oacc_declare): New definition.
	(struct gfc_namespace): Change type.
	(enum gfc_exec_op): Add EXEC_OACC_DECLARE.
	(struct gfc_code): New field.
	* module.c (enum ab_attribute): Add AB_OACC_DECLARE_CREATE,
	AB_OACC_DECLARE_COPYIN, AB_OACC_DECLARE_DEVICEPTR,
	AB_OACC_DECLARE_DEVICE_RESIDENT, AB_OACC_DECLARE_LINK
	(attr_bits): Add new initializers.
	(mio_symbol_attribute): Handle new atributes.
	* openmp.c (gfc_free_oacc_declare_clauses): New function.
	(gfc_match_oacc_clause_link: Likewise.
	(OMP_CLAUSE_LINK): New definition.
	(gfc_match_omp_clauses): Handle OMP_CLAUSE_LINK.
	(OACC_DECLARE_CLAUSES): Add OMP_CLAUSE_LINK
	(gfc_match_oacc_declare): Add checking and module handling.
	(resolve_omp_clauses): Add array initializer.
	(gfc_resolve_oacc_declare): Reimplement.
	* parse.c (case_decl): Add ST_OACC_DECLARE.
	(parse_spec): Remove handling.
	(parse_progunit): Remove handling.
	* parse.h (struct gfc_state_data): Change type.
	* resolve.c (gfc_resolve_blocks): Handle EXEC_OACC_DECLARE.
	* st.c (gfc_free_statement): Handle EXEC_OACC_DECLARE.
	* symbol.c (check_conflict): Add conflict checks.
	(gfc_add_oacc_declare_create, gfc_add_oacc_declare_copyin, 
	gfc_add_oacc_declare_deviceptr, gfc_add_oacc_declare_device_resident):
	New functions.
	(gfc_copy_attr): Handle new symbols.
	* trans-decl.c (add_clause, find_module_oacc_declare_clauses,
	finish_oacc_declare): New functions.
	(gfc_generate_function_code): Replace with call.
	* trans-openmp.c (gfc_trans_oacc_declare): Reimplement.
	(gfc_trans_oacc_directive): Handle EXEC_OACC_DECLARE.
	* trans-stmt.c (gfc_trans_block_construct): Replace with call.
	* trans-stmt.h (gfc_trans_oacc_declare): Remove argument.
	* trans.c (trans_code): Handle EXEC_OACC_DECLARE.

	gcc/testsuite
	* gfortran.dg/goacc/declare-1.f95: Update test.
	* gfortran.dg/goacc/declare-2.f95: New test.

	libgomp/
	* testsuite/libgomp.oacc-fortran/declare-1.f90: New test.
	* testsuite/libgomp.oacc-fortran/declare-2.f90: Likewise.
	* testsuite/libgomp.oacc-fortran/declare-3.f90: Likewise.
	* testsuite/libgomp.oacc-fortran/declare-4.f90: Likewise.
	* testsuite/libgomp.oacc-fortran/declare-5.f90: Likewise.

Co-Authored-By: Cesar Philippidis <cesar@codesourcery.com>

From-SVN: r230722
2015-11-22 16:45:38 +00:00

69 lines
1.1 KiB
Fortran

! { dg-do run { target openacc_nvidia_accel_selected } }
module globalvars
implicit none
real b
!$acc declare link (b)
end module globalvars
program test
use openacc
use globalvars
implicit none
real a
real c
!$acc declare link (c)
if (acc_is_present (b) .neqv. .false.) call abort
if (acc_is_present (c) .neqv. .false.) call abort
a = 0.0
b = 1.0
!$acc parallel copy (a) copyin (b)
b = b + 4.0
a = b
!$acc end parallel
if (a .ne. 5.0) call abort
if (acc_is_present (b) .neqv. .false.) call abort
a = 0.0
!$acc parallel copy (a) create (b)
b = 4.0
a = b
!$acc end parallel
if (a .ne. 4.0) call abort
if (acc_is_present (b) .neqv. .false.) call abort
a = 0.0
!$acc parallel copy (a) copy (b)
b = 4.0
a = b
!$acc end parallel
if (a .ne. 4.0) call abort
if (b .ne. 4.0) call abort
if (acc_is_present (b) .neqv. .false.) call abort
a = 0.0
!$acc parallel copy (a) copy (b) copy (c)
b = 4.0
c = b
a = c
!$acc end parallel
if (a .ne. 4.0) call abort
if (acc_is_present (b) .neqv. .false.) call abort
end program test