OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / whole_file_32.f90
1 ! { dg-do compile }
2 ! { dg-options "-O -finline-small-functions" }
3 ! Tests the fix for PR45743 in which the compilation failed with an ICE
4 ! internal compiler error: verify_stmts failed.  The source is the essential
5 ! part of whole_file_3.f90.
6 !
7 ! Contributed by Zdenek Sojka  <zsojka@seznam.cz>
8 !
9       SUBROUTINE PHLOAD (READER,*)
10       IMPLICIT NONE
11       EXTERNAL         READER
12       CALL READER (*1)
13  1    RETURN 1
14       END SUBROUTINE
15
16       program test
17       EXTERNAL R
18       CALL PHLOAD (R, *999) ! This one is OK
19  999  continue
20       END program test