Fortran allows the INTRINSIC attribute to be specified with a distinct attribute statement, and also as part of the attribute list of a type-declaration-stmt. This is an odd case (especially as the declared type is mandated to be ignored if it doesn't match the type of the intrinsic function) that can lead to odd error messages and crashes, since the rest of name resolution expects that intrinsics with explicit declarations will have been declared with INTRINSIC attribute statements. Resolve by handling an "inline" INTRINSIC attribute as a special case while processing a type-declaration-stmt, so that real, intrinsic :: acos, asin, atan is processed exactly as if it had been intrinsic acos, asin, atan; real acos, asin, atan Fixes https://github.com/llvm/llvm-project/issues/86382.
66 lines
3.2 KiB
Fortran
66 lines
3.2 KiB
Fortran
! RUN: %python %S/test_errors.py %s %flang_fc1
|
|
! C801 The same attr-spec shall not appear more than once in a given
|
|
! type-declaration-stmt.
|
|
!
|
|
! R801 type-declaration-stmt ->
|
|
! declaration-type-spec [[, attr-spec]... ::] entity-decl-list
|
|
! attr-spec values are:
|
|
! PUBLIC, PRIVATE, ALLOCATABLE, ASYNCHRONOUS, CODIMENSION, CONTIGUOUS,
|
|
! DIMENSION (array-spec), EXTERNAL, INTENT (intent-spec), INTRINSIC,
|
|
! BIND(C), OPTIONAL, PARAMETER, POINTER, PROTECTED, SAVE, TARGET, VALUE,
|
|
! VOLATILE
|
|
module m
|
|
|
|
!WARNING: Attribute 'PUBLIC' cannot be used more than once
|
|
real, public, allocatable, public :: publicVar
|
|
!WARNING: Attribute 'PRIVATE' cannot be used more than once
|
|
real, private, allocatable, private :: privateVar
|
|
!WARNING: Attribute 'ALLOCATABLE' cannot be used more than once
|
|
real, allocatable, allocatable :: allocVar
|
|
!WARNING: Attribute 'ASYNCHRONOUS' cannot be used more than once
|
|
real, asynchronous, public, asynchronous :: asynchVar
|
|
!ERROR: Attribute 'CODIMENSION' cannot be used more than once
|
|
real, codimension[*], codimension[*] :: codimensionVar
|
|
!WARNING: Attribute 'CONTIGUOUS' cannot be used more than once
|
|
real, contiguous, pointer, contiguous :: contigVar(:)
|
|
!ERROR: Attribute 'DIMENSION' cannot be used more than once
|
|
real, dimension(5), dimension(5) :: arrayVar
|
|
!WARNING: Attribute 'EXTERNAL' cannot be used more than once
|
|
real, external, external :: externFunc
|
|
!WARNING: Attribute 'INTRINSIC' cannot be used more than once
|
|
!ERROR: An interface name with BIND attribute must be specified if the BIND attribute is specified in a procedure declaration statement
|
|
real, intrinsic, bind(c), intrinsic :: cos
|
|
!WARNING: Attribute 'BIND(C)' cannot be used more than once
|
|
integer, bind(c), volatile, bind(c) :: bindVar
|
|
!WARNING: Attribute 'PARAMETER' cannot be used more than once
|
|
real, parameter, parameter :: realConst = 4.3
|
|
!WARNING: Attribute 'POINTER' cannot be used more than once
|
|
real, pointer, pointer :: realPtr
|
|
!WARNING: Attribute 'PROTECTED' cannot be used more than once
|
|
real, protected, protected :: realProt
|
|
!WARNING: Attribute 'SAVE' cannot be used more than once
|
|
real, save, save :: saveVar
|
|
!WARNING: Attribute 'TARGET' cannot be used more than once
|
|
real, target, target :: targetVar
|
|
!WARNING: Attribute 'VOLATILE' cannot be used more than once
|
|
real, volatile, volatile :: volatileVar
|
|
|
|
contains
|
|
subroutine testTypeDecl(arg1, arg2, arg3, arg4, arg5, arg6)
|
|
!WARNING: Attribute 'INTENT(IN)' cannot be used more than once
|
|
real, intent(in), intent(in) :: arg1
|
|
!WARNING: Attribute 'INTENT(OUT)' cannot be used more than once
|
|
real, intent(out), intent(out) :: arg2
|
|
!WARNING: Attribute 'INTENT(INOUT)' cannot be used more than once
|
|
real, intent(inout), intent(inout) :: arg3
|
|
!WARNING: Attribute 'OPTIONAL' cannot be used more than once
|
|
integer, optional, intent(in), optional :: arg4
|
|
!WARNING: Attribute 'VALUE' cannot be used more than once
|
|
integer, value, intent(in), value :: arg5
|
|
!ERROR: Attributes 'INTENT(IN)' and 'INTENT(INOUT)' conflict with each other
|
|
integer, intent(in), pointer, intent(inout) :: arg6
|
|
|
|
arg2 =3.5
|
|
end subroutine testTypeDecl
|
|
end module m
|