diff options
Diffstat (limited to 'gcc/testsuite/gfortran.dg/whole_file_20.f03')
-rw-r--r-- | gcc/testsuite/gfortran.dg/whole_file_20.f03 | 33 |
1 files changed, 33 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/whole_file_20.f03 b/gcc/testsuite/gfortran.dg/whole_file_20.f03 new file mode 100644 index 000000000..61e2a4df9 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/whole_file_20.f03 @@ -0,0 +1,33 @@ +! { dg-do compile } +! { dg-options "-fwhole-file -fcoarray=single" } +! +! Procedures with dummy arguments that are coarrays or polymorphic +! must have an explicit interface in the calling routine. +! + +MODULE classtype + type :: t + integer :: comp + end type +END MODULE + +PROGRAM main + USE classtype + CLASS(t), POINTER :: tt + + INTEGER :: coarr[*] + + CALL coarray(coarr) ! { dg-error " must have an explicit interface" } + CALL polymorph(tt) ! { dg-error " must have an explicit interface" } +END PROGRAM + +SUBROUTINE coarray(a) + INTEGER :: a[*] +END SUBROUTINE + +SUBROUTINE polymorph(b) + USE classtype + CLASS(t) :: b +END SUBROUTINE + +! { dg-final { cleanup-modules "classtype" } } |