Files
clang-p2996/flang/test/Semantics/call13.f90
Peter Klausler 29fd3e2aa8 [flang] Allow polymorphic actual to implicit interface (#70873)
Semantics is emitting an error when an actual argument to a procedure
that has an implicit interface has a polymorphic type. This is too
general; while TYPE(*) and CLASS(*) unlimited polymorphic items require
the presence of an explicit procedure interface, CLASS(T) data can be
passed over an implicit interface to a procedure expecting a
corresponding dummy argument with TYPE(T), so long as T is not
parameterized.

(Only XLF handles this usage correctly among other Fortran compilers.)

(Making this work in the case of an actual CLASS(T) array may well
require additional changes in lowering to copy data to/from a temporary
buffer to ensure contiguity when the actual type of the array is an
extension of T.)
2023-11-13 13:31:58 -08:00

43 lines
1.6 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
! Test 15.4.2.2 constraints and restrictions for calls to implicit
! interfaces
subroutine s(assumedRank, coarray, class, classStar, typeStar)
type :: t
end type
real :: assumedRank(..), coarray[*]
class(t) :: class
class(*) :: classStar
type(*) :: typeStar
type :: pdt(len)
integer, len :: len
end type
type(pdt(1)) :: pdtx
!ERROR: Invalid specification expression: reference to impure function 'implicit01'
real :: array(implicit01()) ! 15.4.2.2(2)
!ERROR: Keyword 'keyword=' may not appear in a reference to a procedure with an implicit interface
call implicit10(1, 2, keyword=3) ! 15.4.2.2(1)
!ERROR: Assumed rank argument requires an explicit interface
call implicit11(assumedRank) ! 15.4.2.2(3)(c)
!ERROR: Coarray argument requires an explicit interface
call implicit12(coarray) ! 15.4.2.2(3)(d)
!ERROR: Parameterized derived type actual argument requires an explicit interface
call implicit13(pdtx) ! 15.4.2.2(3)(e)
call implicit14(class) ! ok
!ERROR: Unlimited polymorphic actual argument requires an explicit interface
call implicit15(classStar) ! 15.4.2.2(3)(f)
!ERROR: Assumed type actual argument requires an explicit interface
call implicit16(typeStar) ! 15.4.2.2(3)(f)
!ERROR: TYPE(*) dummy argument may only be used as an actual argument
if (typeStar) then
endif
!ERROR: TYPE(*) dummy argument may only be used as an actual argument
classStar = typeStar ! C710
!ERROR: TYPE(*) dummy argument may only be used as an actual argument
typeStar = classStar ! C710
end subroutine