OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [entry_12.f90] - Diff between revs 302 and 384

Only display areas with differences | Details | Blame | View Log

Rev 302 Rev 384
! { dg-do run }
! { dg-do run }
! Tests the fix for pr31609, where module procedure entries found
! Tests the fix for pr31609, where module procedure entries found
! themselves in the wrong namespace.  This test checks that all
! themselves in the wrong namespace.  This test checks that all
! combinations of generic and specific calls work correctly.
! combinations of generic and specific calls work correctly.
!
!
! Contributed by Paul Thomas  as comment #8 to the pr.
! Contributed by Paul Thomas  as comment #8 to the pr.
!
!
MODULE ksbin1_aux_mod
MODULE ksbin1_aux_mod
  interface foo
  interface foo
    module procedure j
    module procedure j
  end interface
  end interface
  interface bar
  interface bar
    module procedure k
    module procedure k
  end interface
  end interface
  interface foobar
  interface foobar
    module procedure j, k
    module procedure j, k
  end interface
  end interface
  CONTAINS
  CONTAINS
    FUNCTION j ()
    FUNCTION j ()
    j = 1
    j = 1
    return
    return
    ENTRY k (i)
    ENTRY k (i)
    k = 2
    k = 2
    END FUNCTION j
    END FUNCTION j
END MODULE ksbin1_aux_mod
END MODULE ksbin1_aux_mod
    use ksbin1_aux_mod
    use ksbin1_aux_mod
    if (any ((/foo (), bar (99), foobar (), foobar (99), j (), k (99)/) .ne. &
    if (any ((/foo (), bar (99), foobar (), foobar (99), j (), k (99)/) .ne. &
             (/1, 2, 1, 2, 1, 2/))) Call abort ()
             (/1, 2, 1, 2, 1, 2/))) Call abort ()
end
end
! { dg-final { cleanup-modules "ksbin1_aux_mod" } }
! { dg-final { cleanup-modules "ksbin1_aux_mod" } }
 
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.