RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / matmul_19.f90
blobc4549240c1f53e1f006112ed223cb4ec7f99cd3a
1 ! { dg-do run }
2 ! { dg-options "-finline-matmul-limit=0" }
3 ! PR 86704 - this used to segfault.
5 program testmaticovenasobeni
6 implicit none
8 character(len=10) :: line
9 write (unit=line,fmt=*) testmatmul(120,1,3)
11 contains
13 function testmatmul(m,n,o)
14 integer, intent(in) :: m,n,o
15 real :: A(n,m),B(n,o),C(m,o)
16 logical :: testmatmul
18 call random_number(A)
19 call random_number(B)
21 C=matmul(transpose(A),B)
22 testmatmul=.true.
23 end function
25 end program testmaticovenasobeni