summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/do_check_8.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/do_check_8.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/do_check_8.f9059
1 files changed, 59 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/do_check_8.f90 b/gcc/testsuite/gfortran.dg/do_check_8.f90
new file mode 100644
index 0000000000..458ae40b60
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/do_check_8.f90
@@ -0,0 +1,59 @@
+! { dg-do compile }
+! PR 55593 - bogus error with generic subroutines
+module foo
+ implicit none
+ interface sub
+ subroutine sub2(i)
+ integer, intent(in) :: i
+ end subroutine sub2
+ subroutine sub(i)
+ integer, dimension(:), intent(out) :: i
+ end subroutine sub
+ end interface sub
+
+ interface tub2
+ subroutine tub2(i)
+ integer, intent(in) :: i
+ end subroutine tub2
+ subroutine tub(i)
+ integer, dimension(:), intent(out) :: i
+ end subroutine tub
+ end interface tub2
+
+ interface func
+ integer function ifunc(i)
+ integer, intent(in) :: i
+ end function ifunc
+ integer function func(i)
+ integer, intent(in) :: i(:)
+ end function func
+ end interface func
+
+ interface igunc
+ integer function igunc(i)
+ integer, intent(in) :: i
+ end function igunc
+ integer function gunc(i)
+ integer, intent(in) :: i(:)
+ end function gunc
+ end interface igunc
+end module foo
+
+program main
+ use foo
+ implicit none
+ integer :: i
+ do i=1,10
+ call sub(i)
+ call tub2(i)
+ end do
+ do i=1,10
+ print *,func(i)
+ print *,igunc(i)
+ end do
+
+ do undeclared=1,10 ! { dg-error "has no IMPLICIT type" }
+ call sub(undeclared)
+ end do
+end program main
+! { dg-final { cleanup-modules "foo" } }