fix pr/45972
[official-gcc.git] / gcc / testsuite / gfortran.dg / typebound_proc_10.f03
blob3f372c815f23f14abde163171543500e2b4a972d
1 ! { dg-do compile }
3 ! Type-bound procedures
4 ! Test for resolution errors with DEFERRED, namely checks about invalid
5 ! overriding and taking into account inherited DEFERRED bindings.
6 ! Also check that DEFERRED attribute is saved to module correctly.
8 MODULE m1
9   IMPLICIT NONE
11   ABSTRACT INTERFACE
12     SUBROUTINE intf ()
13     END SUBROUTINE intf
14   END INTERFACE
16   TYPE, ABSTRACT :: abstract_type
17   CONTAINS
18     PROCEDURE(intf), DEFERRED, NOPASS :: def
19     PROCEDURE, NOPASS :: nodef => realproc
20   END TYPE abstract_type
22 CONTAINS
24   SUBROUTINE realproc ()
25   END SUBROUTINE realproc
27 END MODULE m1
29 MODULE m2
30   USE m1
31   IMPLICIT NONE
33   TYPE, ABSTRACT, EXTENDS(abstract_type) :: sub_type1
34   CONTAINS
35     PROCEDURE(intf), DEFERRED, NOPASS :: nodef ! { dg-error "must not be DEFERRED" }
36   END TYPE sub_type1
38   TYPE, EXTENDS(abstract_type) :: sub_type2 ! { dg-error "must be ABSTRACT" }
39   END TYPE sub_type2
41 END MODULE m2
43 ! { dg-final { cleanup-modules "m1" } }