PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / unlimited_polymorphic_28.f90
blobb474a243233d997a13952c64677037c2d04f605b
1 ! { dg-do compile }
3 ! PR 82257: ICE in gfc_typename(), compare_rank(), resolve_structure_cons()
5 module m1
7 implicit none
9 type,abstract :: c_base
10 contains
11 procedure(i1),private,deferred :: f_base
12 end type c_base
14 abstract interface
15 function i1(this) result(res)
16 import
17 class(c_base),intent(IN) :: this
18 class(c_base), pointer :: res
19 end function i1
20 end interface
22 type,abstract,extends(c_base) :: c_derived
23 contains
24 procedure :: f_base => f_derived ! { dg-error "Type mismatch in function result \\(CLASS\\(\\*\\)/CLASS\\(c_base\\)\\)" }
25 end type c_derived
27 contains
29 function f_derived(this) result(res) ! { dg-error "must be dummy, allocatable or pointer" }
30 class(c_derived), intent(IN) :: this
31 class(*) :: res
32 end function f_derived
34 end module m1
36 module m2
38 implicit none
40 type :: t
41 contains
42 procedure :: p
43 end type t
45 contains
47 class(*) function p(this) ! { dg-error "must be dummy, allocatable or pointer" }
48 class(t), intent(IN) :: this
49 end function p
51 end module m2