df161b697c
gcc/fortran/ 2010-07-24 Tobias Burnus <burnus@net-b.de> * options.c (gfc_init_options): Enable -fwhole-file by default. * interface.c (compare_parameter): Assume a Hollerith constant is compatible with all other argument types. libgomp/ 2010-07-24 Tobias Burnus <burnus@net-b.de> * testsuite/libgomp.fortran/appendix-a/a.28.5.f90: Add -w to silence -fwhole-file warning. gcc/testsuite/ 2010-07-24 Tobias Burnus <burnus@net-b.de> * gfortran.dg/func_decl_4.f90: Split test into two ... * gfortran.dg/func_decl_5.f90: ... parts. * gfortran.dg/common_resize_1.f: xfail two warnings (cf. PR 45045). * gfortran.dg/bounds_temporaries_1.f90: Add new dg-warning. * gfortran.dg/global_references_1.f90: Add new dg-warning. * gfortran.dg/generic_actual_arg.f90: Add new dg-warning. * gfortran.dg/entry_17.f90: Remove no-longer needed dg-warning. * gfortran.dg/used_before_typed_4.f90: Add new dg-warning. * gfortran.dg/bounds_check_strlen_1.f90: Add new dg-warning. * gfortran.dg/intrinsic_std_1.f90: Split by remove tree dump ... * gfortran.dg/intrinsic_std_6.f90: ... and create a dump test. * gfortran.dg/sizeof.f90: Make test valid. * gfortran.dg/pr20865.f90: Add new dg-error. * gfortran.dg/integer_exponentiation_2.f90: Add new dg-warnings. * gfortran.dg/g77/19990218-0.f: Ditto. * gfortran.dg/g77/19990218-1.f: Ditto. * gfortran.dg/g77/970625-2.f: Ditto. * gfortran.dg/pr37243.f: Fix function declaration. * gfortran.dg/use_only_1.f90: Fix implicit typing. * gfortran.dg/loc_1.f90: Fix pointer datatype. From-SVN: r162491
35 lines
1.1 KiB
Fortran
35 lines
1.1 KiB
Fortran
! { dg-do compile }
|
|
! { dg-options "-w" }
|
|
!
|
|
! "-w" added as libgomp/testsuite seemingly cannot parse with
|
|
! dg-warning Fortran's output. Fortran warns for "call sub1(a)"
|
|
! that there is a "Rank mismatch in argument 'x'".
|
|
|
|
SUBROUTINE SUB1(X)
|
|
DIMENSION X(10)
|
|
! This use of X does not conform to the
|
|
! specification. It would be legal Fortran 90,
|
|
! but the OpenMP private directive allows the
|
|
! compiler to break the sequence association that
|
|
! A had with the rest of the common block.
|
|
FORALL (I = 1:10) X(I) = I
|
|
END SUBROUTINE SUB1
|
|
PROGRAM A28_5
|
|
COMMON /BLOCK5/ A
|
|
DIMENSION B(10)
|
|
EQUIVALENCE (A,B(1))
|
|
! the common block has to be at least 10 words
|
|
A=0
|
|
!$OMP PARALLEL PRIVATE(/BLOCK5/)
|
|
! Without the private clause,
|
|
! we would be passing a member of a sequence
|
|
! that is at least ten elements long.
|
|
! With the private clause, A may no longer be
|
|
! sequence-associated.
|
|
CALL SUB1(A)
|
|
!$OMP MASTER
|
|
PRINT *, A
|
|
!$OMP END MASTER
|
|
!$OMP END PARALLEL
|
|
END PROGRAM A28_5
|