OSDN Git Service

PR target/51393
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / pr50769.f90
1 ! { dg-do compile }
2 ! { dg-options "-O2 -ftree-tail-merge -fno-delete-null-pointer-checks -fno-guess-branch-probability" }
3 !
4 ! based on testsuite/gfortran.dg/alloc_comp_optional_1.f90,
5 ! which was contributed by David Kinniburgh <davidkinniburgh@yahoo.co.uk>
6 !
7 program test_iso
8   type ivs
9      character(LEN=1), dimension(:), allocatable :: chars
10   end type ivs
11   type(ivs) :: v_str
12   integer :: i
13   call foo(v_str, i)
14   if (v_str%chars(1) .ne. "a") call abort
15   if (i .ne. 0) call abort
16   call foo(flag = i)
17   if (i .ne. 1) call abort
18 contains
19   subroutine foo (arg, flag)
20     type(ivs), optional, intent(out) :: arg
21     integer :: flag
22     if (present(arg)) then
23       arg = ivs([(char(i+96), i = 1,10)])
24       flag = 0
25     else
26       flag = 1
27     end if
28   end subroutine
29 end
30