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

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [interface_derived_type_1.f90] - Diff between revs 149 and 154

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

Rev 149 Rev 154
! { dg-do compile }
! { dg-do compile }
! Test the fix for PR20903, in which derived types could be host associated within
! Test the fix for PR20903, in which derived types could be host associated within
! interface bodies.
! interface bodies.
!
!
! Contributed by Joost VandeVondele 
! Contributed by Joost VandeVondele 
!
!
module test
module test
  implicit none
  implicit none
  type fcnparms
  type fcnparms
    integer :: i
    integer :: i
  end type fcnparms
  end type fcnparms
contains
contains
  subroutine sim_1(func1,params)
  subroutine sim_1(func1,params)
    interface
    interface
      function func1(fparams)
      function func1(fparams)
        type(fcnparms) :: fparams ! { dg-error "not been declared within the interface" }
        type(fcnparms) :: fparams ! { dg-error "not been declared within the interface" }
        real :: func1
        real :: func1
      end function func1
      end function func1
    end interface
    end interface
    type(fcnparms)     :: params
    type(fcnparms)     :: params
   end subroutine sim_1
   end subroutine sim_1
  subroutine sim_2(func2,params)
  subroutine sim_2(func2,params)
    interface
    interface
      function func2(fparams)     ! This is OK because of the derived type decl.
      function func2(fparams)     ! This is OK because of the derived type decl.
        type fcnparms
        type fcnparms
          integer :: i
          integer :: i
        end type fcnparms
        end type fcnparms
        type(fcnparms)  :: fparams
        type(fcnparms)  :: fparams
        real :: func2
        real :: func2
      end function func2
      end function func2
    end interface
    end interface
    type(fcnparms)      :: params ! This is OK, of course
    type(fcnparms)      :: params ! This is OK, of course
   end subroutine sim_2
   end subroutine sim_2
end module  test
end module  test
module type_decl
module type_decl
  implicit none
  implicit none
  type fcnparms
  type fcnparms
    integer :: i
    integer :: i
  end type fcnparms
  end type fcnparms
end module type_decl
end module type_decl
subroutine sim_3(func3,params)
subroutine sim_3(func3,params)
  use type_decl
  use type_decl
  interface
  interface
    function func3(fparams)
    function func3(fparams)
      use type_decl
      use type_decl
      type(fcnparms)   :: fparams ! This is OK - use associated
      type(fcnparms)   :: fparams ! This is OK - use associated
      real :: func3
      real :: func3
    end function func3
    end function func3
  end interface
  end interface
  type(fcnparms)       :: params  !         -ditto-
  type(fcnparms)       :: params  !         -ditto-
end subroutine sim_3
end subroutine sim_3
! { dg-final { cleanup-modules "test type_decl" } }
! { dg-final { cleanup-modules "test type_decl" } }
 
 

powered by: WebSVN 2.1.0

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