@@ -320,55 +320,51 @@ pure function slice_char(string, first, last, stride) result(sliced_string)
320320 integer , intent (in ), optional :: first, last, stride
321321 integer :: first_index, last_index, stride_vector, strides_taken, length_string, i, j
322322 character (len= :), allocatable :: sliced_string
323-
324323 length_string = len (string)
325- if (length_string > 0 ) then
326- first_index = 1
327- last_index = length_string
328- stride_vector = 1
329-
330- if (present (stride)) then
331- if (stride /= 0 ) then
332- if (stride < 0 ) then
333- first_index = length_string
334- last_index = 1
335- end if
336- stride_vector = stride
324+
325+ first_index = 1
326+ last_index = length_string
327+ stride_vector = 1
328+
329+ if (present (stride)) then
330+ if (stride /= 0 ) then
331+ if (stride < 0 ) then
332+ first_index = length_string
333+ last_index = 1
337334 end if
338- else
339- if (present (first) .and. present (last)) then
340- if (last < first) then
341- stride_vector = - 1
342- end if
335+ stride_vector = stride
336+ end if
337+ else
338+ if (present (first) .and. present (last)) then
339+ if (last < first) then
340+ stride_vector = - 1
343341 end if
344342 end if
343+ end if
345344
346- if (present (first)) then
347- first_index = first
348- end if
349- if (present (last)) then
350- last_index = last
351- end if
352-
353- if (stride_vector > 0 ) then
354- first_index = max (first_index, 1 )
355- last_index = min (last_index, length_string)
356- else
357- first_index = min (first_index, length_string)
358- last_index = max (last_index, 1 )
359- end if
360-
361- strides_taken = floor ( real (last_index - first_index)/ real (stride_vector) )
362- allocate (character (len= max (0 , strides_taken + 1 )) :: sliced_string)
363-
364- j = 1
365- do i = first_index, last_index, stride_vector
366- sliced_string(j:j) = string (i:i)
367- j = j + 1
368- end do
345+ if (present (first)) then
346+ first_index = first
347+ end if
348+ if (present (last)) then
349+ last_index = last
350+ end if
351+
352+ if (stride_vector > 0 ) then
353+ first_index = max (first_index, 1 )
354+ last_index = min (last_index, length_string)
369355 else
370- sliced_string = " "
356+ first_index = min (first_index, length_string)
357+ last_index = max (last_index, 1 )
371358 end if
359+
360+ strides_taken = floor ( real (last_index - first_index)/ real (stride_vector) )
361+ allocate (character (len= max (0 , strides_taken + 1 )) :: sliced_string)
362+
363+ j = 1
364+ do i = first_index, last_index, stride_vector
365+ sliced_string(j:j) = string (i:i)
366+ j = j + 1
367+ end do
372368 end function slice_char
373369
374370
0 commit comments