PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / host_assoc_function_3.f90
blobcb898bc48ec713dad8fbb8ead59ed4694487441e
1 ! { dg-do run }
2 ! Tests the fix for the bug PR33233, in which the reference to 'x'
3 ! in 'inner' wrongly host-associated with the variable 'x' rather
4 ! than the function.
6 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
8 MODULE m
9 REAL :: x(3) = (/ 1.5, 2.5, 3.5 /)
10 CONTAINS
11 SUBROUTINE s
12 if (x(2) .eq. 2.5) STOP 1
13 CONTAINS
14 FUNCTION x(n, m)
15 integer, optional :: m
16 if (present(m)) then
17 x = REAL(n)**m
18 else
19 x = 0.0
20 end if
21 END FUNCTION
22 END SUBROUTINE s
23 END MODULE m
24 use m
25 call s
26 end