Files
clang-p2996/flang/test/Semantics/resolve73.f90
Peter Klausler 41a964cff0 [flang] Settle ambiguity between C795 and C721
C721 says that a type parameter value of '*' is permitted in the type-spec
for a named constant; C795 says that such type parameters are allowed
in type-specs only for a few kinds of things, not including named
constants.  The interpretation seems to depend on context, with C721
applying to intrinsic types (i.e., character) and C795 applying only
to derived types.

Differential Revision: https://reviews.llvm.org/D146586
2023-03-27 17:37:30 -07:00

49 lines
1.7 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
! C721 A type-param-value of * shall be used only
! * to declare a dummy argument,
! * to declare a named constant,
! * in the type-spec of an ALLOCATE statement wherein each allocate-object is
! a dummy argument of type CHARACTER with an assumed character length,
! * in the type-spec or derived-type-spec of a type guard statement (11.1.11),
! or
! * in an external function, to declare the character length parameter of the function result.
! Note also C795 for derived types (C721 applies to intrinsic types)
subroutine s(arg)
character(len=*), pointer :: arg
character*(*), parameter :: cvar1 = "abc"
character*4, cvar2
character(len=4_4) :: cvar3
!ERROR: An assumed (*) type parameter may be used only for a (non-statement function) dummy argument, associate name, character named constant, or external function result
character(len=*) :: cvar4
type derived(param)
integer, len :: param
class(*), allocatable :: x
end type
type(derived(34)) :: a
interface
function fun()
character(len=4) :: fun
end function fun
end interface
type t(len)
integer, len :: len
end type
!ERROR: An assumed (*) type parameter may be used only for a (non-statement function) dummy argument, associate name, character named constant, or external function result
type(t(*)), parameter :: p2 = t(123)() ! C795
select type (ax => a%x)
type is (integer)
print *, "hello"
type is (character(len=*))
print *, "hello"
class is (derived(param=*))
print *, "hello"
class default
print *, "hello"
end select
allocate (character(len=*) :: arg)
end subroutine s