OSDN Git Service

PR c++/9335
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / nesting_2.f90
1 ! check to make the nested function dawsonseries_v gets the correct
2 ! fake return decl and that the outer (dawson_v) has an assignment of
3 ! just the fake return decl for real and not the inner's return decl.
4 ! { dg-do compile }
5 FUNCTION dawson_v()
6   IMPLICIT NONE
7   REAL  :: dawson_v
8   dawson_v = 1.0
9
10   CONTAINS
11     FUNCTION dawsonseries_v()
12       IMPLICIT NONE
13       REAL, DIMENSION(1) :: dawsonseries_v
14       dawsonseries_v=1.0
15     END FUNCTION dawsonseries_v
16 END FUNCTION dawson_v