OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

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

Go to most recent revision | Only display areas with differences | Details | Blame | View Log

Rev 302 Rev 384
! { dg-do compile }
! { dg-do compile }
!
!
! PR fortran/34137
! PR fortran/34137
!
!
! Entry was previously not possible in a module.
! Entry was previously not possible in a module.
! Checks also whether the different result combinations
! Checks also whether the different result combinations
! work properly.
! work properly.
!
!
module m2
module m2
  implicit none
  implicit none
contains
contains
function func(a)
function func(a)
  implicit none
  implicit none
  integer :: a, func
  integer :: a, func
  real :: func2
  real :: func2
  func = a*8
  func = a*8
  return
  return
entry ent(a) result(func2)
entry ent(a) result(func2)
  ent = -a*4.0 ! { dg-error "is not a variable" }
  ent = -a*4.0 ! { dg-error "is not a variable" }
  return
  return
end function func
end function func
end module m2
end module m2
module m3
module m3
  implicit none
  implicit none
contains
contains
function func(a) result(res)
function func(a) result(res)
  implicit none
  implicit none
  integer :: a, res
  integer :: a, res
  real :: func2
  real :: func2
  res = a*12
  res = a*12
  return
  return
entry ent(a) result(func2)
entry ent(a) result(func2)
  ent = -a*6.0 ! { dg-error "is not a variable" }
  ent = -a*6.0 ! { dg-error "is not a variable" }
  return
  return
end function func
end function func
end module m3
end module m3
 
 

powered by: WebSVN 2.1.0

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