Peter Klausler 35e8624519
[flang] Silence impossible error about SMP interface incompatibility (#112054)
It is possible for the compiler to emit an impossible error message
about dummy argument character length incompatibility in the case of a
MODULE SUBROUTINE or FUNCTION defined later in a submodule with MODULE
PROCEDURE, when the character length is defined by USE association in
its interface. The checking for separate module procedure interface
compatibility needs to use a more flexible check than just operator== on
a semantics::ParamValue.
2024-10-15 14:22:48 -07:00

24 lines
385 B
Fortran

!RUN: %flang -fsyntax-only %s 2>&1 | FileCheck --allow-empty %s
!Ensure no bogus error message about incompatible character length
!CHECK-NOT: error
module m1
integer :: n = 1
end
module m2
interface
module subroutine s(a,b)
use m1
character(n) :: a
character(n) :: b
end
end interface
end
submodule(m2) m2s1
contains
module procedure s
end
end