111
|
1 ! { dg-do compile }
|
|
2 ! Test the patch for PR29992. The standard requires that a
|
|
3 ! module procedure be contained in the same scope as the
|
|
4 ! interface or is use associated to it(12.3.2.1).
|
|
5 !
|
|
6 ! Contributed by Daniel Franke <franke.daniel@gmail.com>
|
|
7 !
|
|
8 MODULE class_foo_type
|
|
9 TYPE :: foo
|
|
10 INTEGER :: dummy
|
|
11 END TYPE
|
|
12 contains
|
|
13 SUBROUTINE bar_init_set_int(this, value)
|
|
14 TYPE(foo), INTENT(out) :: this
|
|
15 integer, intent(in) :: value
|
|
16 this%dummy = value
|
|
17 END SUBROUTINE
|
|
18 END MODULE
|
|
19
|
|
20 MODULE class_foo
|
|
21 USE class_foo_type, ONLY: foo, bar_init_set_int
|
|
22
|
|
23 INTERFACE foo_init
|
|
24 MODULE PROCEDURE foo_init_default ! { dg-error "is not a module procedure" }
|
|
25 END INTERFACE
|
|
26
|
|
27 INTERFACE bar_init
|
|
28 MODULE PROCEDURE bar_init_default, bar_init_set_int ! These are OK
|
|
29 END INTERFACE
|
|
30
|
|
31 INTERFACE
|
|
32 SUBROUTINE foo_init_default(this)
|
|
33 USE class_foo_type, ONLY: foo
|
|
34 TYPE(foo), INTENT(out) :: this
|
|
35 END SUBROUTINE
|
|
36 END INTERFACE
|
|
37
|
|
38 contains
|
|
39 SUBROUTINE bar_init_default(this)
|
|
40 TYPE(foo), INTENT(out) :: this
|
|
41 this%dummy = 42
|
|
42 END SUBROUTINE
|
|
43
|
|
44 END MODULE
|