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/matmul_9.f90 | 47 ++++++++++++++++++++++++++++++++++ 1 file changed, 47 insertions(+) create mode 100644 gcc/testsuite/gfortran.dg/matmul_9.f90 (limited to 'gcc/testsuite/gfortran.dg/matmul_9.f90') diff --git a/gcc/testsuite/gfortran.dg/matmul_9.f90 b/gcc/testsuite/gfortran.dg/matmul_9.f90 new file mode 100644 index 000000000..bf2a299c8 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/matmul_9.f90 @@ -0,0 +1,47 @@ +! { dg-do run } +! { dg-options "-fdump-tree-original" } +! +! PR fortran/56318 +! +! Contributed by Alberto Luaces +! +SUBROUTINE mass_matrix + DOUBLE PRECISION,PARAMETER::m1=1.d0 + DOUBLE PRECISION,DIMENSION(3,2),PARAMETER::A1=reshape([1.d0,0.d0, 0.d0, & + 0.d0,1.d0, 0.d0],[3,2]) + DOUBLE PRECISION,DIMENSION(2,2),PARAMETER::Mel=reshape([1.d0/3.d0, 0.d0, & + 0.d0, 1.d0/3.d0],[2,2]) + + DOUBLE PRECISION,DIMENSION(3,3)::MM1 + + MM1=m1*matmul(A1,matmul(Mel,transpose(A1))) + !print '(3f8.3)', MM1 + if (any (abs (MM1 & + - reshape ([1.d0/3.d0, 0.d0, 0.d0, & + 0.d0, 1.d0/3.d0, 0.d0, & + 0.d0, 0.d0, 0.d0], & + [3,3])) > epsilon(1.0d0))) & + call abort () +END SUBROUTINE mass_matrix + +program name + implicit none + integer, parameter :: A(3,2) = reshape([1,2,3,4,5,6],[3,2]) + integer, parameter :: B(2,3) = reshape([3,17,23,31,43,71],[2,3]) + integer, parameter :: C(3) = [-5,-7,-21] + integer, parameter :: m1 = 1 + +! print *, matmul(B,C) + if (any (matmul(B,C) /= [-1079, -1793])) call abort() +! print *, matmul(C,A) + if (any (matmul(C,A) /= [-82, -181])) call abort() +! print '(3i5)', m1*matmul(A,B) + if (any (m1*matmul(A,B) /= reshape([71,91,111, 147,201,255, 327,441,555],& + [3,3]))) & + call abort() + call mass_matrix +end program name + +! { dg-final { scan-tree-dump-times "matmul" 0 "original" } } +! { dg-final { cleanup-tree-dump "original" } } + -- cgit v1.2.3