AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / inline_matmul_22.f90
blob702e32e74671cb03d493fe70772cbb41627756ec
1 ! { dg-do compile }
2 ! { dg-additional-options "-ffrontend-optimize" }
3 ! PR 84270 - this used to be rejected.
4 ! Test case by Michael Weinert
6 module fp_precision
8 integer, parameter :: fp = selected_real_kind(13)
10 end module fp_precision
12 subroutine lhcal(nrot,orth,ngpts,vgauss,vr_0)
14 use fp_precision ! floating point precision
16 implicit none
18 !---> rotation matrices and rotations (input)
19 integer, intent(in) :: nrot
20 ! real(kind=fp), intent(in) :: orth(3,3,nrot) ! fine at all -O
21 real(kind=fp), intent(in) :: orth(3,3,*)
23 !---> gaussian integration points
24 integer, intent(in) :: ngpts
25 real(kind=fp), intent(in) :: vgauss(3,*)
27 !---> output results
28 real(kind=fp), intent(out) :: vr_0(3)
30 real(kind=fp) :: v(3),vr(3)
31 integer :: n,nn
33 vr_0 = 0
34 do nn=1,ngpts
35 v(:) = vgauss(:,nn)
36 !---> apply rotations
37 do n=2,nrot
38 vr = matmul( orth(:,:,n), v )
39 vr_0 = vr_0 + vr
40 enddo
41 enddo
43 return
44 end subroutine lhcal