RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / bounds_check_9.f90
blobe98042dc2bebcfa0db58cfeff7bf2073726bcc43
1 ! { dg-do run }
2 ! { dg-options "-fbounds-check" }
3 ! PR fortran/31119
5 module sub_mod
6 contains
7 elemental subroutine set_optional(i,idef,iopt)
8 integer, intent(out) :: i
9 integer, intent(in) :: idef
10 integer, intent(in), optional :: iopt
11 if (present(iopt)) then
12 i = iopt
13 else
14 i = idef
15 end if
16 end subroutine set_optional
18 subroutine sub(ivec)
19 integer, intent(in), optional :: ivec(:)
20 integer :: ivec_(2)
21 call set_optional(ivec_,(/1,2/))
22 if (any (ivec_ /= (/1, 2/))) STOP 1
23 call set_optional(ivec_,(/1,2/),ivec)
24 if (present (ivec)) then
25 if (any (ivec_ /= ivec)) STOP 2
26 else
27 if (any (ivec_ /= (/1, 2/))) STOP 3
28 end if
29 end subroutine sub
30 end module sub_mod
32 program main
33 use sub_mod, only: sub
34 call sub()
35 call sub((/4,5/))
36 end program main