gcc/libgomp/testsuite/libgomp.fortran/pr32359.f90
Tobias Burnus 5349080dd3 re PR fortran/32359 (incorrect error: Threadprivate isn't SAVEd (implicit save attribute undefined))
gcc/fortran/
2007-07-05  Daniel Franke  <franke.daniel@gmail.com>
	    Tobias Burnus  <burnus@net-b.de>

	PR fortran/32359
	* gfortran.h (symbol_attribute): Change save attribute into an enum.
	* decl.c (add_init_expr_to_sym): Set it to SAVE_IMPLICIT.
	* symbol.c (gfc_add_save): Check for SAVE_EXPLICIT.
	* resolve.c (resolve_fl_variable): Check for SAVE_EXPLICIT.
	(resolve_symbol): Allow OMP threadprivate with
	initialization SAVEd and save_all variable.
	* trans-decl.c (gfc_finish_var_decl): Remove obsolete sym->value check.


libgomp/
2007-07-05  Tobias Burnus  <burnus@net-b.de>

	PR fortran/32359
	* testsuite/libgomp.fortran/pr32359.f90: New.

gcc/testsuite/
2007-07-05  Tobias Burnus  <burnus@net-b.de>

	PR fortran/32359
	* gfortran.dg/module_md5_1.f90: Update MD5 number.

From-SVN: r126366
2007-07-05 14:51:51 +02:00

35 lines
658 B
Fortran

! { dg-do compile }
!
! PR fortran/32359
! Contributed by Bill Long <longb@cray.com>
subroutine test
use omp_lib
implicit none
integer, parameter :: NT = 4
integer :: a
save
!$omp threadprivate(a)
a = 1
!$ call omp_set_num_threads(NT)
!$omp parallel
print *, omp_get_thread_num(), a
!$omp end parallel
end subroutine test
! Derived from OpenMP test omp1/F2_6_2_8_5i.f90
use omp_lib
implicit none
integer, parameter :: NT = 4
integer :: a = 1
!$omp threadprivate(a)
!$ call omp_set_num_threads(NT)
!$omp parallel
print *, omp_get_thread_num(), a
!$omp end parallel
END