From 554fd8c5195424bdbcabf5de30fdc183aba391bd Mon Sep 17 00:00:00 2001 From: upstream source tree Date: Sun, 15 Mar 2015 20:14:05 -0400 Subject: obtained gcc-4.6.4.tar.bz2 from upstream website; verified gcc-4.6.4.tar.bz2.sig; imported gcc-4.6.4 source tree from verified upstream tarball. downloading a git-generated archive based on the 'upstream' tag should provide you with a source tree that is binary identical to the one extracted from the above tarball. if you have obtained the source via the command 'git clone', however, do note that line-endings of files in your working directory might differ from line-endings of the respective files in the upstream repository. --- gcc/testsuite/gfortran.dg/assumed_size_refs_1.f90 | 64 +++++++++++++++++++++++ 1 file changed, 64 insertions(+) create mode 100644 gcc/testsuite/gfortran.dg/assumed_size_refs_1.f90 (limited to 'gcc/testsuite/gfortran.dg/assumed_size_refs_1.f90') diff --git a/gcc/testsuite/gfortran.dg/assumed_size_refs_1.f90 b/gcc/testsuite/gfortran.dg/assumed_size_refs_1.f90 new file mode 100644 index 000000000..1adfd3d5c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/assumed_size_refs_1.f90 @@ -0,0 +1,64 @@ +!==================assumed_size_refs_1.f90================== +! { dg-do compile } +! Test the fix for PR25029, PR21256 in which references to +! assumed size arrays without an upper bound to the last +! dimension were generating no error. The first version of +! the patch failed in DHSEQR, as pointed out by Toon Moene +! in http://gcc.gnu.org/ml/fortran/2005-12/msg00466.html +! +! Contributed by Paul Thomas +! +program assumed_size_test_1 + implicit none + real a(2, 4) + + a = 1.0 + call foo (a) + +contains + subroutine foo(m) + real, target :: m(1:2, *) + real x(2,2,2) + real, external :: bar + real, pointer :: p(:,:), q(:,:) + allocate (q(2,2)) + +! PR25029 + p => m ! { dg-error "upper bound in the last dimension" } + q = m ! { dg-error "upper bound in the last dimension" } + +! PR21256( and PR25060) + m = 1 ! { dg-error "upper bound in the last dimension" } + + m(1,1) = 2.0 + x = bar (m) + x = fcn (m) ! { dg-error "upper bound in the last dimension" } + m(:, 1:2) = fcn (q) + call sub (m, x) ! { dg-error "upper bound in the last dimension" } + call sub (m(1:2, 1:2), x) ! { dg-error "Incompatible ranks in elemental procedure" } + print *, p + + call DHSEQR(x) + + end subroutine foo + + elemental function fcn (a) result (b) + real, intent(in) :: a + real :: b + b = 2.0 * a + end function fcn + + elemental subroutine sub (a, b) + real, intent(inout) :: a, b + b = 2.0 * a + end subroutine sub + + SUBROUTINE DHSEQR( WORK ) + REAL WORK( * ) + EXTERNAL DLARFX + INTRINSIC MIN + WORK( 1 ) = 1.0 + CALL DLARFX( MIN( 1, 8 ), WORK ) + END SUBROUTINE DHSEQR + +end program assumed_size_test_1 -- cgit v1.2.3