Peter Klausler a3e9d3c2c7
[flang] Allow reference to earlier generic in later interface
Name resolutions defers all resolution and checking of specific procedures
in non-type-bound generic interfaces to the end of the specification part.
This prevents expression analysis of references to generic functions in
specification expressions in interfaces from resolving.

Example (now a new test case in modfile07.f90):
```
  module m12
    interface generic
      module procedure specific
    end interface
    interface
      module subroutine s(a1,a2)
        character(*) a1
        character(generic(a1)) a2   ! <--
      end
    end interface
   contains
    pure integer function specific(x)
      character(*), intent(in) :: x
      specific = len(x)
    end
  end
```

The solution is to partially resolve specific procedures as they are
defined for each generic, when they can be resolved, with the final
pass at the end of the specification part to finish up any forward
references and emit the necessary error messages.

Making this fix caused some issues in module file output, which have
all been resolved by making this simplifying change: generics are
now all emitted to module file specification parts as their own
group of declarations at the end of the specification part,
followed only by namelists and COMMON blocks.

Differential Revision: https://reviews.llvm.org/D157346
2023-08-08 12:19:53 -07:00

61 lines
1.5 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
module m
interface foo
real function s1(x)
real x
end
!ERROR: 's2' is not a module procedure
module procedure s2
!ERROR: 's3' is not a procedure
procedure s3
!ERROR: Procedure 's1' is already specified in generic 'foo'
procedure s1
end interface
interface
real function s4(x,y)
real, intent(in) :: x,y
end function
complex function s2(x,y)
complex, intent(in) :: x,y
end function
end interface
generic :: bar => s4
generic :: bar => s2
!ERROR: Procedure 's4' is already specified in generic 'bar'
generic :: bar => s4
generic :: operator(.foo.)=> s4
generic :: operator(.foo.)=> s2
!ERROR: Procedure 's4' is already specified in generic 'OPERATOR(.foo.)'
generic :: operator(.foo.)=> s4
end module
module m2
interface
integer function f(x, y)
logical, intent(in) :: x, y
end function
end interface
generic :: operator(+)=> f
!ERROR: Procedure 'f' is already specified in generic 'OPERATOR(+)'
generic :: operator(+)=> f
end
module m3
interface operator(.ge.)
procedure f
end interface
interface operator(>=)
!ERROR: Procedure 'f' is already specified in generic 'OPERATOR(.GE.)'
procedure f
end interface
generic :: operator(>) => f
!ERROR: Procedure 'f' is already specified in generic 'OPERATOR(>)'
generic :: operator(.gt.) => f
contains
logical function f(x, y) result(result)
logical, intent(in) :: x, y
result = .true.
end
end