view gcc/testsuite/gfortran.dg/type_to_class_2.f03 @ 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 }
!
! Test the fix for PR64757.
!
! Contributed by Michael Lee Rilee  <mike@rilee.net>
!
  type :: Test
    integer :: i
  end type

  type :: TestReference
     class(Test), allocatable :: test
  end type

  type(TestReference) :: testList
  type(test) :: x

  testList = TestReference(Test(99))  ! ICE in fold_convert_loc was here

  x = testList%test

  select type (y => testList%test)    ! Check vptr set
    type is (Test)
      if (x%i .ne. y%i) STOP 1
    class default
      STOP 2
  end select
end