Imported Upstream version 4.8.1
[platform/upstream/gcc48.git] / gcc / testsuite / gfortran.dg / optional_assumed_charlen_1.f90
1 ! { dg-do compile }
2 ! Tests the fix for PR29284 in which an ICE would occur in converting
3 ! the call to a suboutine with an assumed character length, optional
4 ! dummy that is not present.
5 !
6 ! Contributed by Rakuen Himawari  <rakuen_himawari@yahoo.co.jp>
7 !
8       MODULE foo
9       CONTAINS
10         SUBROUTINE sub1(a)
11           CHARACTER (LEN=*), OPTIONAL :: a
12           WRITE(*,*) 'foo bar'
13         END SUBROUTINE sub1
14
15       SUBROUTINE sub2
16         CALL sub1()
17       END SUBROUTINE sub2
18
19      END MODULE foo