aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_operator_14.f90
blob: 86c65d77f3e3f671ffed97a2fb463df53cde9909 (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
! { dg-do compile }
!
! PR fortran/52024
!
! The test case was segfaulting before
!

module m_sort
  implicit none
  type, abstract :: sort_t
  contains
    generic :: operator(.gt.) => gt_cmp
    procedure :: gt_cmp
    end type sort_t
contains
  logical function gt_cmp(a,b)
    class(sort_t), intent(in) :: a, b
    gt_cmp = .true.
  end function gt_cmp
end module

module test
  use m_sort
  implicit none
  type, extends(sort_t) :: sort_int_t
    integer :: i
  contains
    generic :: operator(.gt.) => gt_cmp_int ! { dg-error "are ambiguous" }
    procedure :: gt_cmp_int
  end type
contains
  logical function gt_cmp_int(a,b) result(cmp)
    class(sort_int_t), intent(in) :: a, b
    if (a%i > b%i) then
      cmp = .true.
     else
      cmp = .false.
     end if
  end function gt_cmp_int
end module

! { dg-final { cleanup-tree-dump "m_sort test" } }