view gcc/testsuite/gfortran.dg/interface_29.f90 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
!
! PR 36947: Attributes not fully checked comparing actual vs dummy procedure
!
! Contributed by Tobias Burnus <burnus@net-b.de>

module m
interface foo
  module procedure one, two
end interface foo
contains
subroutine one(op,op2)
    interface
      subroutine op(x, y)
        complex, intent(in)  :: x(:)
        complex, intent(out) :: y(:)
      end subroutine op
      subroutine op2(x, y)
        complex, intent(in)  :: x(:)
        complex, intent(out) :: y(:)
      end subroutine op2
    end interface
end subroutine one
subroutine two(ops,i,j)
    interface
      subroutine op(x, y)
        complex, intent(in)  :: x(:)
        complex, intent(out) :: y(:)
      end subroutine op
    end interface
    real :: i,j
end subroutine two
end module m

module test
contains
subroutine bar()
  use m
  call foo(precond_prop,prop2)
end subroutine bar
  subroutine precond_prop(x, y)
    complex, intent(in)  :: x(:)
    complex, intent(out) :: y(:)
  end subroutine
  subroutine prop2(x, y)
    complex, intent(in)  :: x(:)
    complex, intent(out) :: y(:)
  end subroutine
end module test