Peter Klausler df3e5f18d0 [flang] Emit missing IMPORTs in module file interfaces
When a symbol from the enclosing scope is necessary to declare
a procedure or procedure pointer dummy argument or function result
for a procedure interface, note it in the collection of symbols to
be imported when scanning that interface.

Differential Revision: https://reviews.llvm.org/D132683
2022-08-25 15:05:31 -07:00

56 lines
1.2 KiB
Fortran

! RUN: %python %S/test_modfile.py %s %flang_fc1
! Ensure that interfaces, which are internal to procedures and are used to
! define the interface of dummy or return value procedures, are included in
! .mod files.
module m
implicit none
contains
function f(x)
real, intent(in) :: x
abstract interface
subroutine used_int(x, p)
implicit none
real, intent(out) :: x
interface
subroutine inner_int(x)
implicit none
real, intent(out) :: x
end subroutine inner_int
end interface
procedure(inner_int) :: p
end subroutine used_int
pure logical function unused_int(i)
implicit none
integer, intent(in) :: i
end function unused_int
end interface
procedure(used_int), pointer :: f
f => null()
contains
subroutine internal()
end subroutine internal
end function f
end module m
!Expect: m.mod
!module m
!contains
!function f(x)
!real(4),intent(in)::x
!abstract interface
!subroutine used_int(x,p)
!real(4),intent(out)::x
!interface
!subroutine inner_int(x)
!real(4),intent(out)::x
!end
!end interface
!procedure(inner_int)::p
!end
!end interface
!procedure(used_int),pointer::f
!end
!end