2018-07-05 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_character_20.f90
blob85e2a2ca6c4cd5120dfe296e518a3a42ccd7dae1
1 ! { dg-do compile }
3 ! Test the fix for PR86408.
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
7 module m
9 implicit none
11 type, abstract :: t
12 contains
13 procedure(ifc), deferred :: tbf
14 procedure :: tbs
15 end type
17 abstract interface
18 function ifc(x) result(str)
19 import :: t
20 class(t) :: x
21 character(len=:), allocatable :: str
22 end function
23 end interface
25 contains
27 subroutine tbs(x)
28 class(t) :: x
29 print *, x%tbf()
30 end subroutine
32 end