Files
clang-p2996/flang/test/Semantics/generic07.f90
Peter Klausler 3d1157000d [flang] Restore error status for many indistinguishable specifics (#79927)
A recent patch to allow pFUnit to compile softened the diagnostic about
indistinguishable specific procedures to a portability warning. It turns
out that this was overkill -- for specific procedures containing no
optional or unlimited polymorphic dummy data arguments, a diagnosis of
"indistinguishable" can still be a hard error.

So adjust the analysis to be tri-state: two procedures are either
definitely distinguishable, definitely indistinguishable without
optionals or unlimited polymorphics, or indeterminate. Emit errors as
before for the definitely indistinguishable cases; continue to emit
portability warnings for the indeterminate cases.

When this patch is merged, all but one of the dozen or so tests that I
disabled in llvm-test-suite can be re-enabled.
2024-01-29 17:31:35 -08:00

95 lines
1.7 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
module m1
type :: t1
sequence
real :: x
end type
type :: t2
sequence
real :: x
end type
type :: t3
real :: x
end type
type :: t4
real, private :: x
end type
contains
subroutine s1a(x)
type(t1), intent(in) :: x
end
subroutine s2a(x)
type(t2), intent(in) :: x
end
subroutine s3a(x)
type(t3), intent(in) :: x
end
subroutine s4a(x)
type(t4), intent(in) :: x
end
end
module m2
type t10
integer n
contains
procedure :: f
generic:: operator(+) => f
end type
contains
elemental type(t10) function f(x,y)
class(t10), intent(in) :: x, y
f%n = x%n + y%n
end
end
module m3
use m2, only: rt10 => t10
end
program test
use m1, only: s1a, s2a, s3a, s4a
use m2, only: t10
use m3, only: rt10 ! alias for t10, ensure no distinguishability error
type :: t1
sequence
integer :: x ! distinct type
end type
type :: t2
sequence
real :: x
end type
type :: t3 ! no SEQUENCE
real :: x
end type
type :: t4
real :: x ! not PRIVATE
end type
interface distinguishable1
procedure :: s1a, s1b
end interface
interface distinguishable2
procedure :: s1a, s1b
end interface
interface distinguishable3
procedure :: s1a, s1b
end interface
!ERROR: Generic 'indistinguishable' may not have specific procedures 's2b' and 's2a' as their interfaces are not distinguishable
interface indistinguishable
procedure :: s2a, s2b
end interface
contains
subroutine s1b(x)
type(t1), intent(in) :: x
end
subroutine s2b(x)
type(t2), intent(in) :: x
end
subroutine s3b(x)
type(t3), intent(in) :: x
end
subroutine s4b(x)
type(t4), intent(in) :: x
end
end