Plugins: Add label-text.h to CPPLIB_H so it will be installed [PR115288]
[official-gcc.git] / gcc / testsuite / gfortran.dg / do_check_17.f90
blob02b8993de3879b862523fd4622cae2e126e87077
1 ! { dg-do compile }
2 ! PR 99345 - this used to cause an ICE.
3 ! Original test case by Matthias Klose
4 program main
5 implicit none
6 integer :: iq,nq,recl
7 DO iq = 1, nq
8 CALL calc_upper_fan (iq)
9 ENDDO
10 CONTAINS
11 SUBROUTINE calc_upper_fan (iq)
12 INTEGER :: iq
13 INTEGER :: recl
14 INQUIRE(IOLENGTH=recl) iq
15 END SUBROUTINE calc_upper_fan
16 END