2 ! { dg-options "-fbounds-check" }
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
16 end subroutine set_optional
19 integer, intent(in
), optional
:: ivec(:)
21 call set_optional(ivec_
,(/1,2/))
22 if (any (ivec_
/= (/1, 2/))) call abort
23 call set_optional(ivec_
,(/1,2/),ivec
)
24 if (present (ivec
)) then
25 if (any (ivec_
/= ivec
)) call abort
27 if (any (ivec_
/= (/1, 2/))) call abort
33 use sub_mod
, only
: sub
37 ! { dg-final { cleanup-modules "sub_mod" } }