nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr71047.f08
blob61a0ad4dc31c411b9cfaa724180842165417b322
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! Fortran/PR71047
7 module m
8  implicit none
10  type, abstract :: c_abstr
11   integer :: i = 0
12  end type c_abstr
14  type, extends(c_abstr) :: t_a
15   class(c_abstr), allocatable :: f
16  end type t_a
18  type, extends(c_abstr) :: t_b
19  end type t_b
21 contains
23  subroutine set(y,x)
24   class(c_abstr), intent(in)  :: x
25   type(t_a),      intent(out) :: y
26    allocate( y%f , source=x )
27  end subroutine set
29 end module m
32 program p
33  use m
34  implicit none
36  type(t_a) :: res
37  type(t_b) :: var
39   call set( res , var )
40   write(*,*) res%i
42 end program p
45 ! Check to ensure the vtable is actually initialized.
47 ! { dg-final { scan-tree-dump "t_a\\.\\d+\\.f\\._vptr =" "original" } }