2 ! { dg-options "-fbounds-check" }
5 ! Ensure that too long or matching string lengths don't trigger the runtime
6 ! error for matching string lengths, if the dummy argument is neither
7 ! POINTER nor ALLOCATABLE or assumed-shape.
8 ! Also check that absent OPTIONAL arguments don't trigger the check.
13 SUBROUTINE test (str
, opt
)
15 CHARACTER(len
=5) :: str
16 CHARACTER(len
=5), OPTIONAL
:: opt
24 CALL test ('abcde') ! String length matches.
25 CALL test ('abcdef') ! String too long, is ok.
28 ! { dg-final { cleanup-modules "m" } }