Imported Upstream version 4.8.1
[platform/upstream/gcc48.git] / gcc / testsuite / gfortran.dg / whole_file_20.f03
1 ! { dg-do compile }
2 ! { dg-options "-fwhole-file -fcoarray=single" }
3 !
4 ! Procedures with dummy arguments that are coarrays or polymorphic
5 ! must have an explicit interface in the calling routine.
6 !
7
8 MODULE classtype
9   type :: t
10     integer :: comp
11   end type
12 END MODULE
13
14 PROGRAM main
15   USE classtype
16   CLASS(t), POINTER :: tt
17
18   INTEGER :: coarr[*]
19
20   CALL coarray(coarr)         ! { dg-error " must have an explicit interface" }
21   CALL polymorph(tt)          ! { dg-error " must have an explicit interface" }
22 END PROGRAM
23
24 SUBROUTINE coarray(a)
25   INTEGER :: a[*]
26 END SUBROUTINE
27
28 SUBROUTINE polymorph(b)
29   USE classtype
30   CLASS(t) :: b
31 END SUBROUTINE