aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/function_types_2.f90
blob: 0c1603939448f0ee790f89089f09dafbf1f500a3 (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 compile }
! Tests the fix for PR34431 in which function TYPEs that were
! USE associated would cause an error.
!
! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
!
module m1
  integer :: hh
  type t
    real :: r
  end type t
end module m1

module m2
  type t
    integer :: k
  end type t
end module m2

module m3
contains
  type(t) function func()
    use m2
    func%k = 77
  end function func
end module m3

type(t) function a()
  use m1, only: hh
  type t2
    integer :: j
  end type t2
  type t
    logical :: b
  end type t

  a%b = .true.
end function a

type(t) function b()
  use m1, only: hh
  use m2
  use m3
  b = func ()
  b%k = 5
end function b

type(t) function c()
  use m1, only: hh
  type t2
    integer :: j
  end type t2
  type t
    logical :: b
  end type t

  c%b = .true.
end function c

program main
  type t
    integer :: m
  end type t
contains
  type(t) function a1()
    use m1, only: hh
    type t2
      integer :: j
    end type t2
    type t
      logical :: b
    end type t

    a1%b = .true.
  end function a1

  type(t) function b1()
    use m1, only: hh
    use m2, only: t
! NAG f95 believes that the host-associated type(t)
! should be used:
!   b1%m = 5
! However, I (Tobias Burnus) believe that the use-associated one should
! be used:
    b1%k = 5
  end function b1

  type(t) function c1()
    use m1, only: hh
    type t2
      integer :: j
    end type t2
    type t
      logical :: b
    end type t

    c1%b = .true.
  end function c1

  type(t) function d1()
    d1%m = 55
  end function d1
end program main