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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [select_type_10.f03] - Rev 694

Compare with Previous | Blame | View Log

! { dg-do compile }
!
! PR 42167: [OOP] SELECT TYPE with function return value
!
! Contributed by Damian Rouson <damian@rouson.net>

module bar_module

  implicit none
  type :: bar
    real ,dimension(:) ,allocatable :: f
  contains
    procedure :: total
  end type

contains

  function total(lhs,rhs)
    class(bar) ,intent(in) :: lhs
    class(bar) ,intent(in) :: rhs
    class(bar) ,pointer :: total
    select type(rhs)
      type is (bar)
        allocate(bar :: total)
        select type(total)
          type is (bar)
            total%f = lhs%f + rhs%f
        end select
    end select
  end function

end module 

! { dg-final { cleanup-modules "bar_module" } }

Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

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