re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_ptr_result_1.f90
blob6d7e89a7be0b3305585f811f58b9d6124bacb702
1 ! { dg-do run }
3 ! PR 36704: Procedure pointer as function result
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
7 module mo
8 contains
10 function j()
11 implicit none
12 procedure(integer),pointer :: j
13 intrinsic iabs
14 j => iabs
15 end function
17 subroutine sub(y)
18 integer,intent(inout) :: y
19 y = y**2
20 end subroutine
22 end module
25 program proc_ptr_14
26 use mo
27 implicit none
28 intrinsic :: iabs
29 integer :: x
30 procedure(integer),pointer :: p,p2
31 procedure(sub),pointer :: ps
33 p => a()
34 if (p(-1)/=1) STOP 1
35 p => b()
36 if (p(-2)/=2) STOP 2
37 p => c()
38 if (p(-3)/=3) STOP 3
40 ps => d()
41 x = 4
42 call ps(x)
43 if (x/=16) STOP 4
45 p => dd()
46 if (p(-4)/=4) STOP 5
48 ps => e(sub)
49 x = 5
50 call ps(x)
51 if (x/=25) STOP 6
53 p => ee()
54 if (p(-5)/=5) STOP 7
55 p => f()
56 if (p(-6)/=6) STOP 8
57 p => g()
58 if (p(-7)/=7) STOP 9
60 ps => h(sub)
61 x = 2
62 call ps(x)
63 if (x/=4) STOP 10
65 p => i()
66 if (p(-8)/=8) STOP 11
67 p => j()
68 if (p(-9)/=9) STOP 12
70 p => k(p2)
71 if (p(-10)/=p2(-10)) STOP 13
73 p => l()
74 if (p(-11)/=11) STOP 14
76 contains
78 function a()
79 procedure(integer),pointer :: a
80 a => iabs
81 end function
83 function b()
84 procedure(integer) :: b
85 pointer :: b
86 b => iabs
87 end function
89 function c()
90 pointer :: c
91 procedure(integer) :: c
92 c => iabs
93 end function
95 function d()
96 pointer :: d
97 external d
98 d => sub
99 end function
101 function dd()
102 pointer :: dd
103 external :: dd
104 integer :: dd
105 dd => iabs
106 end function
108 function e(arg)
109 external :: e,arg
110 pointer :: e
111 e => arg
112 end function
114 function ee()
115 integer :: ee
116 external :: ee
117 pointer :: ee
118 ee => iabs
119 end function
121 function f()
122 pointer :: f
123 interface
124 integer function f(x)
125 integer,intent(in) :: x
126 end function
127 end interface
128 f => iabs
129 end function
131 function g()
132 interface
133 integer function g(x)
134 integer,intent(in) :: x
135 end function g
136 end interface
137 pointer :: g
138 g => iabs
139 end function
141 function h(arg)
142 interface
143 subroutine arg(b)
144 integer,intent(inout) :: b
145 end subroutine arg
146 end interface
147 pointer :: h
148 interface
149 subroutine h(a)
150 integer,intent(inout) :: a
151 end subroutine h
152 end interface
153 h => arg
154 end function
156 function i()
157 pointer :: i
158 interface
159 function i(x)
160 integer :: i,x
161 intent(in) :: x
162 end function i
163 end interface
164 i => iabs
165 end function
167 function k(arg)
168 procedure(integer),pointer :: k,arg
169 k => iabs
170 arg => k
171 end function
173 function l()
174 ! we cannot use iabs directly as it is elemental
175 abstract interface
176 pure function interf_iabs(x)
177 integer, intent(in) :: x
178 end function interf_iabs
179 end interface
180 procedure(interf_iabs),pointer :: l
181 integer :: i
182 l => iabs
183 if (l(-11)/=11) STOP 15
184 end function