blob: 62f3c11ab0405364c9a432301dbab7fc0294a884 [file] [log] [blame]
! { dg-do run }
! { dg-options "-fbounds-check" }
! PR fortran/32036
program test
type t
integer, dimension (5) :: field
end type t
type (t), dimension (2) :: a
integer :: calls
type xyz_type
integer :: x
end type xyz_type
type (xyz_type), dimension(3) :: xyz
character(len=80) :: s
xyz(1)%x = 11111
xyz(2)%x = 0
xyz(3)%x = 0
write(s,*) xyz(bar())
if (trim(adjustl(s)) /= "11111") STOP 1
a(1)%field = 0
a(2)%field = 0
calls = 0
if (sum(a(foo(calls))%field) /= 0) STOP 2
if (calls .ne. 1) STOP 3
contains
function foo (calls)
integer :: calls, foo
calls = calls + 1
foo = 2
end function foo
integer function bar ()
integer, save :: i = 1
bar = i
i = i + 1
end function
end program test