[C++ PATCH] Deprecate -ffriend-injection
[official-gcc.git] / gcc / testsuite / gfortran.dg / function_optimize_8.f90
bloba6fe1036d133837385b79c8fb77efa0fbac51228
1 ! { dg-do compile }
2 ! { dg-options "-O -fdump-tree-original" }
3 module x
4 implicit none
5 contains
6 pure function myfunc(x) result(y)
7 integer, intent(in) :: x
8 integer, dimension(:), allocatable :: y
9 allocate (y(3))
10 y(1) = x
11 y(2) = 2*x
12 y(3) = 3*x
13 end function myfunc
15 pure function mychar(x) result(r)
16 integer, intent(in) :: x
17 character(len=2) :: r
18 r = achar(x + iachar('0')) // achar(x + iachar('1'))
19 end function mychar
20 end module x
22 program main
23 use x
24 implicit none
25 integer :: n
26 character(len=20) :: line
27 n = 3
28 write (unit=line,fmt='(3I2)') myfunc(n) + myfunc(n)
29 if (line /= ' 61218') call abort
30 write (unit=line,fmt='(A)') mychar(2) // mychar(2)
31 if (line /= '2323') call abort
32 end program main
33 ! { dg-final { scan-tree-dump-times "myfunc" 2 "original" } }
34 ! { dg-final { scan-tree-dump-times "mychar" 2 "original" } }