RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / function_optimize_7.f90
bloba8245de4a0953d942a462e66a072873695c988df
1 ! { dg-do compile }
2 ! { dg-options "-O -fdump-tree-original -Warray-temporaries -finline-matmul-limit=0" }
3 subroutine xx(n, m, a, b, c, d, x, z, i, s_in, s_out)
4 implicit none
5 integer, intent(in) :: n, m
6 real, intent(in), dimension(n,n) :: a, b, c
7 real, intent(out), dimension(n,n) :: d
8 real, intent(in), dimension(n,m) :: s_in
9 real, intent(out), dimension(m) :: s_out
10 integer, intent(out) :: i
11 real, intent(inout) :: x
12 real, intent(out) :: z
13 character(60) :: line
14 real, external :: ext_func
15 integer :: one = 1
16 interface
17 elemental function element(x)
18 real, intent(in) :: x
19 real :: elem
20 end function element
21 pure function mypure(x)
22 real, intent(in) :: x
23 integer :: mypure
24 end function mypure
25 elemental impure function elem_impure(x)
26 real, intent(in) :: x
27 real :: elem_impure
28 end function elem_impure
29 end interface
31 d = matmul(a,b) + matmul(a,b) ! { dg-warning "Creating array temporary" }
32 z = sin(x) + cos(x) + sin(x) + cos(x)
33 x = ext_func(a) + 23 + ext_func(a)
34 z = element(x) + element(x)
35 i = mypure(x) - mypure(x)
36 z = elem_impure(x) - elem_impure(x)
37 s_out = sum(s_in,one) + 3.14 / sum(s_in,one) ! { dg-warning "Creating array temporary" }
38 end subroutine xx
39 ! { dg-final { scan-tree-dump-times "matmul_r4" 1 "original" } }
40 ! { dg-final { scan-tree-dump-times "__builtin_sinf" 1 "original" } }
41 ! { dg-final { scan-tree-dump-times "__builtin_cosf" 1 "original" } }
42 ! { dg-final { scan-tree-dump-times "ext_func" 2 "original" } }
43 ! { dg-final { scan-tree-dump-times "element" 1 "original" } }
44 ! { dg-final { scan-tree-dump-times "mypure" 1 "original" } }
45 ! { dg-final { scan-tree-dump-times "elem_impure" 2 "original" } }
46 ! { dg-final { scan-tree-dump-times "sum_r4" 1 "original" } }