diff gcc/testsuite/gfortran.dg/generic_7.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/gcc/testsuite/gfortran.dg/generic_7.f90	Fri Oct 27 22:46:09 2017 +0900
@@ -0,0 +1,26 @@
+! { dg-do compile }
+! Tests the fix for PR29652, in which ambiguous interfaces were not detected
+! with more than two specific procedures in the interface.
+!
+! Contributed by Daniel Franke  <franke.daniel@gmail.com>
+!
+MODULE global
+INTERFACE iface
+  MODULE PROCEDURE sub_a
+  MODULE PROCEDURE sub_b
+  MODULE PROCEDURE sub_c
+END INTERFACE
+CONTAINS
+  SUBROUTINE sub_a(x) ! { dg-error "Ambiguous interfaces" }
+    INTEGER, INTENT(in) :: x
+    WRITE (*,*) 'A: ', x
+  END SUBROUTINE
+  SUBROUTINE sub_b(y) ! { dg-error "Ambiguous interfaces" }
+    INTEGER, INTENT(in) :: y
+    WRITE (*,*) 'B: ', y
+  END SUBROUTINE
+  SUBROUTINE sub_c(x, y)
+    REAL, INTENT(in) :: x, y
+    WRITE(*,*) x, y
+  END SUBROUTINE
+END MODULE