aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_operator_20.f90
blob: 26c49a188eb1a5a58ac4486b14981d92dbdbf72c (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
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
! { dg-do run }
!
! PR 63733: [4.8/4.9/5 Regression] [OOP] wrong resolution for OPERATOR generics
!
! Original test case from Alberto F. Martín Huertas <amartin@cimne.upc.edu>
! Slightly modified by Salvatore Filippone <sfilippone@uniroma2.it>
! Further modified by Janus Weil <janus@gcc.gnu.org>

module overwrite
  type parent
   contains
     procedure :: sum => sum_parent
     generic   :: operator(+) => sum
  end type

  type, extends(parent) ::  child
  contains
    procedure :: sum => sum_child
  end type

contains

  integer function sum_parent(op1,op2)
    implicit none
    class(parent), intent(in) :: op1, op2
    sum_parent = 0
  end function

  integer function sum_child(op1,op2)
    implicit none
    class(child) , intent(in) :: op1
    class(parent), intent(in) :: op2
    sum_child = 1
  end function

end module

program drive
  use overwrite
  implicit none

  type(parent) :: m1, m2
  class(parent), pointer :: mres
  type(child)  :: h1, h2
  class(parent), pointer :: hres

  if (m1 + m2 /= 0) call abort()
  if (h1 + m2 /= 1) call abort()
  if (h1%sum(h2) /= 1) call abort()

end

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