blob: 0c061a23a2370193c1d1941a64717f49e76c5499 [file] [log] [blame]
! { 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