* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_type_proc_pointer_1.f90
blob3fc055e0e9ca56904db55ae555029bbcdfaccb49
1 ! { dg-do compile }
3 ! PR fortran/45170
4 ! PR fortran/52158
6 ! Contributed by Tobias Burnus
8 module test
9 implicit none
10 type t
11 procedure(deferred_len), pointer, nopass :: ppt
12 end type t
13 contains
14 function deferred_len()
15 character(len=:), allocatable :: deferred_len
16 deferred_len = 'abc'
17 end function deferred_len
18 subroutine doIt()
19 type(t) :: x
20 x%ppt => deferred_len
21 if ("abc" /= x%ppt()) call abort()
22 end subroutine doIt
23 end module test
25 use test
26 call doIt ()
27 end