3 ! Torture-test TRIM and LEN_TRIM for correctness.
6 ! Given a total string length and a trimmed length, construct an
7 ! appropriate string and check gfortran gets it right.
9 SUBROUTINE check_trim (full_len
, trimmed_len
)
11 INTEGER, INTENT(IN
) :: full_len
, trimmed_len
12 CHARACTER(LEN
=full_len
) :: string
15 IF (trimmed_len
> 0) THEN
16 string(trimmed_len
:trimmed_len
) = "x"
19 IF (LEN (string
) /= full_len
&
20 .OR
. LEN_TRIM (string
) /= trimmed_len
&
21 .OR
. LEN (TRIM (string
)) /= trimmed_len
&
22 .OR
. TRIM (string
) /= string (1:trimmed_len
)) THEN
23 PRINT *, full_len
, trimmed_len
24 PRINT *, LEN (string
), LEN_TRIM (string
)
27 END SUBROUTINE check_trim
30 ! The main program, check with various combinations.
38 CALL check_trim (i
, j
)