RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_type_proc_pointer_2.f90
blob069c7f28b654675f33929e7327801882c3a404ba
1 ! { dg-do compile }
3 ! PR fortran/45170
4 ! PR fortran/52158
6 module test
7 implicit none
8 type t
9 procedure(deferred_len), pointer, nopass :: ppt
10 end type t
11 contains
12 function deferred_len()
13 character(len=:), allocatable :: deferred_len
14 deferred_len = 'abc'
15 end function deferred_len
16 subroutine doIt()
17 type(t) :: x
18 character(:), allocatable :: temp
19 x%ppt => deferred_len
20 temp = deferred_len()
21 if ("abc" /= temp) STOP 1
22 end subroutine doIt
23 end module test
25 use test
26 call doIt ()
27 end