URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [proc_ptr_29.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do compile }
!
! PR 45366: Problem with procedure pointer dummy in PURE function
!
! Contributed by Marco Restelli <mrestelli@gmail.com>
module m1
implicit none
abstract interface
pure function i_f(x) result(y)
real, intent(in) :: x
real :: y
end function i_f
end interface
end module m1
module m2
use m1, only: i_f
implicit none
contains
pure function i_g(x,p) result(y)
real, intent(in) :: x
procedure(i_f), pointer, intent(in) :: p
real :: y
y = p(x)
end function i_g
end module m2
! { dg-final { cleanup-modules "m1 m2" } }