aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/pr48636.f90
blob: cb5b4d7a553ad7ba3bcc9dcc26b0cabfa33072ee (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
! { dg-do compile }
! { dg-options "-O3 -fdump-ipa-inline-details -fdump-ipa-fnsummary-details -fno-ipa-cp" }

module foo
  implicit none
contains
  subroutine bar(a,x)
    real, dimension(:,:), intent(in) :: a
    real, intent(out) :: x
    integer :: i,j

    x = 0
    do j=1,ubound(a,2)
       do i=1,ubound(a,1)
          x = x + a(i,j)**2
       end do
    end do
  end subroutine bar
end module foo

program main
  use foo
  implicit none
  real, dimension(2,3) :: a
  real :: x
  integer :: i

  data a /1.0, 2.0, 3.0, -1.0, -2.0, -3.0/

  do i=1,2000000
     call bar(a,x)
  end do
  print *,x
end program main

! { dg-final { scan-ipa-dump "bar\[^\\n\]*inline copy in MAIN" "inline" } }
! { dg-final { scan-ipa-dump-times "phi predicate:" 3 "fnsummary" } }
! { dg-final { scan-ipa-dump "IPA hints: loop_iterations" "inline" } }