OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / function_optimize_1.f90
1 ! { dg-do compile }
2 ! { dg-options "-O -fdump-tree-original -Warray-temporaries" }
3 program main
4   implicit none
5   real, dimension(2,2) :: a, b, c, d
6   integer :: i
7   real :: x, z
8   character(60) :: line
9   real, external :: ext_func
10   interface
11      elemental function element(x)
12        real, intent(in) :: x
13        real :: elem
14      end function element
15      pure function mypure(x)
16        real, intent(in) :: x
17        integer :: mypure
18      end function mypure
19      elemental impure function elem_impure(x)
20        real, intent(in) :: x
21        real :: elem_impure
22      end function elem_impure
23   end interface
24
25   data a /2., 3., 5., 7./
26   data b /11., 13., 17., 23./
27   write (unit=line, fmt='(4F7.2)') matmul(a,b)  &
28        & + matmul(a,b)    ! { dg-warning "Creating array temporary" }
29   z = sin(x) + cos(x) + sin(x) + cos(x)
30   print *,z
31   x = ext_func(a) + 23 + ext_func(a)
32   print *,d,x
33   z = element(x) + element(x)
34   print *,z
35   i = mypure(x) - mypure(x)
36   print *,i
37   z = elem_impure(x) - elem_impure(x)
38   print *,z
39 end program main
40 ! { dg-final { scan-tree-dump-times "matmul_r4" 1 "original" } }
41 ! { dg-final { scan-tree-dump-times "__builtin_sinf" 1 "original" } }
42 ! { dg-final { scan-tree-dump-times "__builtin_cosf" 1 "original" } }
43 ! { dg-final { scan-tree-dump-times "ext_func" 2 "original" } }
44 ! { dg-final { scan-tree-dump-times "element" 1 "original" } }
45 ! { dg-final { scan-tree-dump-times "mypure" 1 "original" } }
46 ! { dg-final { scan-tree-dump-times "elem_impure" 2 "original" } }
47 ! { dg-final { cleanup-tree-dump "original" } }