PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_optional_1.f90
blob3961dc2174d91aca9f5abe6a44ab37a9b04e83f6
1 ! { dg-do run }
2 ! Tests the fix for PR38602, a regression caused by a modification
3 ! to the nulling of INTENT_OUT dummies with allocatable components
4 ! that caused a segfault with optional arguments.
6 ! Contributed by David Kinniburgh <davidkinniburgh@yahoo.co.uk>
8 program test_iso
9 type ivs
10 character(LEN=1), dimension(:), allocatable :: chars
11 end type ivs
12 type(ivs) :: v_str
13 integer :: i
14 call foo(v_str, i)
15 if (v_str%chars(1) .ne. "a") STOP 1
16 if (i .ne. 0) STOP 2
17 call foo(flag = i)
18 if (i .ne. 1) STOP 3
19 contains
20 subroutine foo (arg, flag)
21 type(ivs), optional, intent(out) :: arg
22 integer :: flag
23 if (present(arg)) then
24 arg = ivs([(char(i+96), i = 1,10)])
25 flag = 0
26 else
27 flag = 1
28 end if
29 end subroutine
30 end