view gcc/testsuite/gfortran.dg/generic_19.f90 @ 128:fe568345ddd5

fix CbC-example
author mir3636
date Wed, 11 Apr 2018 19:32:28 +0900
parents 04ced10e8804
children 84e7813d76e9
line wrap: on
line source

! { dg-do compile }
! Test the fix for PR42481, in which 'sub' was not recognised as
! a generic interface.
!
! Contributed by William Mitchell < william.mitchell@nist.gov>
!
module mod1
contains
  subroutine sub(x, chr)
    real x
    character(8) chr
    if (trim (chr) .ne. "real") call abort
    if (int (x) .ne. 1) call abort
  end subroutine sub
end module mod1

module mod2
  use mod1
  interface sub
    module procedure sub, sub_int
  end interface sub
contains
  subroutine sub_int(i, chr)
    character(8) chr
    integer i
    if (trim (chr) .ne. "integer") call abort
    if (i .ne. 1) call abort
  end subroutine sub_int
end module mod2

program prog
  use mod1
  use mod2
  call sub(1, "integer ")
  call sub(1.0, "real    ")
end program prog