
In a derived type definition, a type bound procedure declaration statement with neither interface nor attributes is required by constraint C768 to have the optional "::" between the PROCEDURE keyword and the bindings if any binding has a renaming with "=>". The colons are not actually necessary for a correct and unambiguous parse, so emit a warning when they are missing. Differential Revision: https://reviews.llvm.org/D139065
14 lines
302 B
Fortran
14 lines
302 B
Fortran
! RUN: %flang_fc1 -fsyntax-only -pedantic %s 2>&1 | FileCheck %s
|
|
module m
|
|
type t
|
|
contains
|
|
!CHECK: portability: type-bound procedure statement should have '::' if it has '=>'
|
|
procedure p => sub
|
|
end type
|
|
contains
|
|
subroutine sub(x)
|
|
class(t), intent(in) :: x
|
|
end subroutine
|
|
end module
|
|
|