re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / size_optional_dim_1.f90
blobc6e8f761538d8863c118e2ebc810a9c0380928b1
1 ! { dg-do run }
2 ! PR 30865 - passing a subroutine optional argument to size(dim=...)
3 ! used to segfault.
4 program main
5 implicit none
6 integer :: a(2,3)
7 integer :: ires
9 call checkv (ires, a)
10 if (ires /= 6) STOP 1
11 call checkv (ires, a, 1)
12 if (ires /= 2) STOP 2
13 contains
14 subroutine checkv(ires,a1,opt1)
15 integer, intent(out) :: ires
16 integer :: a1(:,:)
17 integer, optional :: opt1
19 ires = size (a1, dim=opt1)
20 end subroutine checkv
21 end program main