OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / function_optimize_5.f90
1 ! { dg-do compile }
2 ! { dg-options "-ffrontend-optimize -Wfunction-elimination" }
3 ! Check the -ffrontend-optimize (in the absence of -O) and
4 ! -Wfunction-elimination options.
5 program main
6   implicit none
7   real, dimension(2,2) :: a, b, c, d
8   integer :: i
9   real :: x, z
10   character(60) :: line
11   real, external :: ext_func
12   interface
13      elemental function element(x)
14        real, intent(in) :: x
15        real :: elem
16      end function element
17      pure function mypure(x)
18        real, intent(in) :: x
19        integer :: mypure
20      end function mypure
21      elemental impure function elem_impure(x)
22        real, intent(in) :: x
23        real :: elem_impure
24      end function elem_impure
25   end interface
26
27   data a /2., 3., 5., 7./
28   data b /11., 13., 17., 23./
29   write (unit=line, fmt='(4F7.2)') matmul(a,b)  & ! { dg-warning "Removing call to function 'matmul'" } 
30        & + matmul(a,b)
31   z = sin(x) + 2.0 + sin(x)  ! { dg-warning "Removing call to function 'sin'" }
32   print *,z
33   x = ext_func(a) + 23 + ext_func(a)
34   print *,d,x
35   z = element(x) + element(x) ! { dg-warning "Removing call to function 'element'" }
36   print *,z
37   i = mypure(x) - mypure(x) ! { dg-warning "Removing call to function 'mypure'" }
38   print *,i
39   z = elem_impure(x) - elem_impure(x)
40   print *,z
41 end program main