c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / elemental_optional_args_7.f90
blobca5689d3fac2c9dd12fef961f7e817a2bf5a2667
1 ! { dg-do run }
3 ! The handling of scalar optional arguments passed to elemental procedure
4 ! did not keep actual arguments and dummy arguments synchronized while
5 ! walking them in gfc_walk_elemental_function_args, leading to a
6 ! null pointer dereference in the generated code.
8 implicit none
10 integer, parameter :: n = 3
12 call do_test
14 contains
16 elemental function five(nonopt1, opt1, nonopt2, opt2)
17 integer, intent(in), optional :: opt1, opt2
18 integer, intent(in) :: nonopt1, nonopt2
19 integer :: five
21 if (.not. present(opt1) .and. .not. present(opt2)) then
22 five = 5
23 else
24 five = -7
25 end if
26 end function five
28 subroutine do_test(opt)
29 integer, optional :: opt
30 integer :: i = -1, a(n) = (/ (i, i=1,n) /)
31 integer :: b(n)
33 b = five(a, nonopt2=i, opt2=opt)
34 if (any(b /= 5)) STOP 1
35 end subroutine do_test
37 end