Skip to content

Commit a44240c

Browse files
klauslerjeanPerier
authored andcommitted
[flang] Downgrade inappropriate error message to a warning
It may not be great practice to pass a procedure (or procedure pointer) with an implicit interface as an actual argument to correspond with a dummy procedure (pointer), but it's not an error. Change to a warning, and modify tests accordingly. Differential Revision: https://reviews.llvm.org/D108932
1 parent cfa4946 commit a44240c

File tree

3 files changed

+32
-11
lines changed

3 files changed

+32
-11
lines changed

flang/lib/Semantics/check-call.cpp

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -553,9 +553,8 @@ static void CheckProcedureArg(evaluate::ActualArgument &arg,
553553
messages.Say(
554554
"Actual procedure argument has an implicit interface "
555555
"which is not known to be compatible with %s which has an "
556-
"explicit interface"_err_en_US,
556+
"explicit interface"_en_US,
557557
dummyName);
558-
return;
559558
}
560559
}
561560
} else { // 15.5.2.9(2,3)

flang/test/Semantics/call09.f90

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -58,9 +58,6 @@ subroutine test1 ! 15.5.2.9(5)
5858
procedure(realfunc), pointer :: p
5959
procedure(intfunc), pointer :: ip
6060
integer, pointer :: intPtr
61-
external :: extfunc
62-
external :: extfuncPtr
63-
pointer :: extfuncPtr
6461
p => realfunc
6562
ip => intfunc
6663
call s01(realfunc) ! ok
@@ -79,8 +76,6 @@ subroutine test1 ! 15.5.2.9(5)
7976
call s01(null(intPtr))
8077
!ERROR: Actual argument associated with procedure dummy argument 'p=' is typeless
8178
call s01(B"0101")
82-
!ERROR: Actual procedure argument has an implicit interface which is not known to be compatible with dummy argument 'p=' which has an explicit interface
83-
call s01(extfunc)
8479
!ERROR: Actual argument associated with procedure pointer dummy argument 'p=' must be a POINTER unless INTENT(IN)
8580
call s02(realfunc)
8681
call s02(p) ! ok
@@ -94,10 +89,6 @@ subroutine test1 ! 15.5.2.9(5)
9489
call s02(null(p))
9590
!ERROR: Actual argument associated with procedure pointer dummy argument 'p=' must be a POINTER unless INTENT(IN)
9691
call s02(sin)
97-
!ERROR: Actual procedure argument has an implicit interface which is not known to be compatible with dummy argument 'p=' which has an explicit interface
98-
call s02(extfunc)
99-
!ERROR: Actual procedure argument has an implicit interface which is not known to be compatible with dummy argument 'p=' which has an explicit interface
100-
call s03(extfuncPtr)
10192
end subroutine
10293

10394
subroutine callsub(s)

flang/test/Semantics/call21.f90

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
! RUN: %flang -fsyntax-only 2>&1 %s | FileCheck %s
2+
! Verifies that warnings issue when actual arguments with implicit
3+
! interfaces are associated with dummy procedures and dummy procedure
4+
! pointers whose interfaces are explicit.
5+
module m
6+
contains
7+
real function realfunc(x)
8+
real, intent(in) :: x
9+
realfunc = x
10+
end function
11+
subroutine s00(p0)
12+
procedure(realfunc) :: p0
13+
end subroutine
14+
subroutine s01(p1)
15+
procedure(realfunc), pointer, intent(in) :: p1
16+
end subroutine
17+
subroutine s02(p2)
18+
procedure(realfunc), pointer :: p2
19+
end subroutine
20+
subroutine test
21+
external :: extfunc
22+
external :: extfuncPtr
23+
pointer :: extfuncPtr
24+
!CHECK: Actual procedure argument has an implicit interface which is not known to be compatible with dummy argument 'p0=' which has an explicit interface
25+
call s00(extfunc)
26+
!CHECK: Actual procedure argument has an implicit interface which is not known to be compatible with dummy argument 'p1=' which has an explicit interface
27+
call s01(extfunc)
28+
!CHECK: Actual procedure argument has an implicit interface which is not known to be compatible with dummy argument 'p2=' which has an explicit interface
29+
call s02(extfuncPtr)
30+
end subroutine
31+
end module

0 commit comments

Comments
 (0)