view gcc/testsuite/gfortran.dg/generic_typebound_operator_1.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
!
! PR fortran/45916
! ICE with generic type-bound operator

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