2 ! PR 49479 - this used not to print anything.
3 ! Test case by Joost VandeVondele.
11 INTEGER, DIMENSION(:), INTENT(IN
), &
14 IF (.not
. PRESENT(data)) STOP 1
15 write (unit
=line
,fmt
='(I5)') size(data)
16 if (line
/= ' 0 ') STOP 2
19 subroutine s_type(data)
20 type(foo
), dimension(:), intent(in
), optional
:: data
22 IF (.not
. PRESENT(data)) STOP 3
23 write (unit
=line
,fmt
='(I5)') size(data)
24 if (line
/= ' 0 ') STOP 4
29 INTEGER, ALLOCATABLE
, DIMENSION(:, :) :: blki
30 type(foo
), allocatable
, dimension(:, :) :: bar
34 CALL S1(RESHAPE(blki
,(/3*N
/)))
35 call s_type(reshape(bar
, (/3*N
/)))