view gcc/testsuite/gfortran.fortran-torture/compile/pr88304-2.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 1830386684a0
children
line wrap: on
line source

! PR fortran/88304

module pr88304
  implicit none
  integer :: p
contains
  function foo (x, y, z, w)
    integer, intent(in) :: x, y
    character(*), optional, intent(out) :: z
    integer, optional, intent(out) :: w
    integer :: foo
    foo = 1
  end function foo
  subroutine bar ()
    integer :: s
    s = baz (1)
  contains
    function baz (u)
      integer, intent(in) :: u
      integer :: baz
      integer :: q
      integer :: r (10)
      r = 0
      baz = 1
      q = foo (p, r(u), w = baz)
    end function baz
  end subroutine bar
end module pr88304