Yes, the standard defines this much more specifically than in the past; but I have found a lot of compilers that do not fully implement it all. One difference I see between compilers is whether the test for zero length is done first or if in the string STR(N:M) does N have to always be at least one so I would assume N has to be at least one to avoid the issue for now myself.
! 9.4.1 Substrings
! A substring is a contiguous portion of a character string (7.4.4).
! R908 substring is parent-string ( substring-range )
! R909 parent-string is scalar-variable-name
! or array-element
! or coindexed-named-object
! or scalar-structure-component
! or scalar-constant
! R910 substring-range is [ scalar-int-expr ] : [ scalar-int-expr ]
! C908 (R909) parent-string shall be of type character.
!
! The value of the ï¬rst scalar-int-expr in substring-range is the
! starting point of the substring and the value of the second one is the
! ending point of the substring. The length of a substring is the number of
! characters in the substring and is MAX (l −f +1, 0), where f and l are
! the starting and ending points, respectively. Let the characters in
! the parent string be numbered 1, 2, 3, ..., n, where n is the length of
! the parent string. Then the characters in the substring are those from
! the parent string from the starting point and proceeding in sequence
! up to and including the ending point. If the starting point is greater
! than the ending point, the substring has length zero; otherwise, both
! the starting point and the ending point shall be within the range 1, 2,
! ..., n. If the starting point is not speciï¬ed, the default value is
! 1. If the ending point is not speciï¬ed, the default value is n.
!
! Examples of character substrings are:
program testit
implicit none
character(len=*),parameter :: all='(*(g0))'
character(len=10) :: b(2)=['abcdefghij','ABCDEFGHIJ']
type struct
character(len=:),allocatable :: name
end type struct
type(struct) :: p
character(len=:),allocatable :: ID
integer :: N,M
print all, 'A) ',B(1)(1:5) ! array element as parent string
p=struct('XYZ')
print all, 'B) ',P%NAME(1:1) ! structure component as parent string
ID='123456789'
print all, 'C) ',ID(4:9) ! scalar variable name as parent string
N=1
M=4
!not implemented in a significant number of compilers
!print all, 'D) ',’0123456789’(N:M) ! character constant as parent string
print all, 'E) ',id(3:2)
print all, 'G) ',id(1:-10)
! argueable
! start index is less than one
print all, 'H) ',id(0:-10)
!print all, 'I) ',id(0:3)
! should fail
!print all, 'J) ',id(-20:-10)
! non-intuitive
!print all, 'F) ',id(3:2:-1) ! not allowed but seems like it should be
end program testit