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/] [external_procedures_2.f90] - Diff between revs 302 and 384

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

Rev 302 Rev 384
! { dg-do compile }
! { dg-do compile }
! Tests the for PR30410, in which the reference to extfunc would
! Tests the for PR30410, in which the reference to extfunc would
! be incorrectly made to the module namespace.
! be incorrectly made to the module namespace.
!
!
! Contributed by Harald Anlauf 
! Contributed by Harald Anlauf 
!
!
module mod1
module mod1
contains
contains
  function eval (func, x1)
  function eval (func, x1)
    real     :: eval, func, x1
    real     :: eval, func, x1
    external :: func
    external :: func
    eval = func (x1)
    eval = func (x1)
  end function eval
  end function eval
end module mod1
end module mod1
!-------------------------------
!-------------------------------
module mod2
module mod2
  use mod1, only : eval
  use mod1, only : eval
  real, external :: extfunc     ! This was referenced as __mod2__extfunc__
  real, external :: extfunc     ! This was referenced as __mod2__extfunc__
contains
contains
  subroutine foo (x0)
  subroutine foo (x0)
    real :: x0, x1
    real :: x0, x1
    x1 = 42
    x1 = 42
    x0 = eval (extfunc, x1)
    x0 = eval (extfunc, x1)
  end subroutine foo
  end subroutine foo
end module mod2
end module mod2
!-------------------------------
!-------------------------------
function extfunc (x)
function extfunc (x)
  real, intent(in) ::  x
  real, intent(in) ::  x
  real             ::  extfunc
  real             ::  extfunc
  extfunc = x
  extfunc = x
end function extfunc
end function extfunc
!-------------------------------
!-------------------------------
program gfcbug53
program gfcbug53
  use mod2, only : foo
  use mod2, only : foo
  real :: x0 = 0
  real :: x0 = 0
  call foo (x0)
  call foo (x0)
  print *, x0
  print *, x0
end program gfcbug53
end program gfcbug53
! { dg-final { cleanup-modules "mod1 mod2" } }
! { dg-final { cleanup-modules "mod1 mod2" } }
 
 

powered by: WebSVN 2.1.0

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