c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / size_optional_dim_1.f90
blobcbf4aa4812ed696917e3b06034002f81397f3c75
1 ! { dg-do run }
2 ! { dg-additional-options "-fdump-tree-original" }
3 ! PR 30865 - passing a subroutine optional argument to size(dim=...)
4 ! used to segfault.
5 program main
6 implicit none
7 integer :: a(2,3)
8 integer :: ires
10 call checkv (ires, a)
11 if (ires /= 6) STOP 1
12 call checkv (ires, a, 1)
13 if (ires /= 2) STOP 2
14 contains
15 subroutine checkv(ires,a1,opt1)
16 integer, intent(out) :: ires
17 integer :: a1(:,:)
18 integer, optional :: opt1
20 ires = size (a1, dim=opt1)
21 end subroutine checkv
22 end program main
24 ! Ensure inline code is generated, cf. PR fortran/94070
25 ! { dg-final { scan-tree-dump-not "_gfortran_size" "original" } }