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/] [proc_decl_10.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 }
! PR33162 INTRINSIC functions as ACTUAL argument
! PR33162 INTRINSIC functions as ACTUAL argument
! Test case adapted from PR by Jerry DeLisle 
! Test case adapted from PR by Jerry DeLisle 
module m
module m
implicit none
implicit none
  interface
  interface
    double precision function my1(x)
    double precision function my1(x)
      double precision, intent(in) :: x
      double precision, intent(in) :: x
    end function my1
    end function my1
  end interface
  end interface
  interface
  interface
    real(kind=4) function my2(x)
    real(kind=4) function my2(x)
      real, intent(in) :: x
      real, intent(in) :: x
    end function my2
    end function my2
  end interface
  end interface
  interface
  interface
    real function  my3(x, y)
    real function  my3(x, y)
      real, intent(in) :: x, y
      real, intent(in) :: x, y
    end function my3
    end function my3
  end interface
  end interface
end module
end module
program test
program test
use m
use m
implicit none
implicit none
procedure(dcos):: my1 ! { dg-error "Cannot change attributes" }
procedure(dcos):: my1 ! { dg-error "Cannot change attributes" }
procedure(cos) :: my2 ! { dg-error "Cannot change attributes" }
procedure(cos) :: my2 ! { dg-error "Cannot change attributes" }
procedure(dprod) :: my3 ! { dg-error "Cannot change attributes" }
procedure(dprod) :: my3 ! { dg-error "Cannot change attributes" }
end program test
end program test
! { dg-final { cleanup-modules "m" } }
! { dg-final { cleanup-modules "m" } }
 
 

powered by: WebSVN 2.1.0

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