aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/use_27.f90
blob: 71d77cc01804f4ca0c9db667556bcade9c541a54 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
! { dg-do run }
!
! PR fortran/45900
! The BTYPEINSTANCE%CALLBACK() typebound call was resolved incorrectly to
! A's CALLBACK procedure instead of B's because the CALLBACK name is ambiguous
! in the MAIN namespace.
!
! Original testcase by someone <ortp21@gmail.com>

module A
implicit none
    type :: aType
    contains
        procedure :: callback
    end type aType
    contains
        subroutine callback( callback_, i )
            implicit none
            class(aType) :: callback_
            integer :: i

            i = 3
        end subroutine callback

        subroutine solver( callback_, i )
            implicit none
            class(aType) :: callback_
            integer :: i

            call callback_%callback(i)
        end subroutine solver
end module A

module B
use A, only: aType
implicit none
    type, extends(aType) :: bType
        integer :: i
    contains
        procedure :: callback
    end type bType
    contains
        subroutine callback( callback_, i )
            implicit none
            class(bType) :: callback_
            integer :: i

            i = 7
        end subroutine callback
end module B

program main
  call test1()
  call test2()

contains

  subroutine test1
    use A
    use B
    implicit none
    type(aType) :: aTypeInstance
    type(bType) :: bTypeInstance
    integer :: iflag

    bTypeInstance%i = 4

    iflag = 0
    call bTypeInstance%callback(iflag)
    if (iflag /= 7) call abort
    iflag = 1
    call solver( bTypeInstance, iflag )
    if (iflag /= 7) call abort

    iflag = 2
    call aTypeInstance%callback(iflag)
    if (iflag /= 3) call abort
  end subroutine test1

  subroutine test2
    use B
    use A
    implicit none
    type(aType) :: aTypeInstance
    type(bType) :: bTypeInstance
    integer :: iflag

    bTypeInstance%i = 4

    iflag = 0
    call bTypeInstance%callback(iflag)
    if (iflag /= 7) call abort
    iflag = 1
    call solver( bTypeInstance, iflag )
    if (iflag /= 7) call abort

    iflag = 2
    call aTypeInstance%callback(iflag)
    if (iflag /= 3) call abort
  end subroutine test2
end program main