OSDN Git Service

2008-03-13 Jerry DeLisle <jvdelisle@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / interface_7.f90
1 ! { dg-do compile }
2 ! One of the tests of the patch for PR30068.
3 !  Taken from the fortran 2003 standard C11.2.
4 !
5 ! The interface is invalid although it is unambiguous because the
6 ! standard explicitly does not require recursion into the formal
7 ! arguments of procedures that themselves are interface arguments.
8 !
9 module xx
10   INTERFACE BAD9
11     SUBROUTINE S9A(X)
12       REAL :: X
13     END SUBROUTINE S9A
14     SUBROUTINE S9B(X)
15       INTERFACE
16         FUNCTION X(A)
17           REAL :: X,A
18         END FUNCTION X
19       END INTERFACE
20     END SUBROUTINE S9B
21     SUBROUTINE S9C(X)
22       INTERFACE
23         FUNCTION X(A)
24           REAL :: X
25           INTEGER :: A
26         END FUNCTION X
27       END INTERFACE
28     END SUBROUTINE S9C  ! { dg-error "Ambiguous interfaces" }
29   END INTERFACE BAD9
30 end module xx
31
32 ! { dg-final { cleanup-modules "xx" } }