aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/select_type_10.f03
blob: 0db9af9599e817c4be1600645c4c3c56f91f0116 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
! { 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