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

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

! { dg-do run }
!
! PR 61767: [OOP] ICE in generate_finalization_wrapper at fortran/class.c:1491
!
! Contributed by <reubendb@gmail.com>

module Communicator_Form
  implicit none
  type :: CommunicatorForm
  contains
    final :: Finalize
  end type
  type :: MessageTemplate
    type ( CommunicatorForm ), pointer :: Communicator
  end type
contains
  subroutine Finalize ( C )
    type ( CommunicatorForm ) :: C
    ! should not be called
    STOP 1
  end subroutine
end module

program p
  use Communicator_Form
  implicit none
  class ( MessageTemplate ), pointer :: M
  allocate(M)
  deallocate(M)
end