@@ -58,9 +58,11 @@ module stdlib_strings
58
58
module procedure :: ends_with_string_char
59
59
module procedure :: ends_with_char_string
60
60
module procedure :: ends_with_char_char
61
- end interface
61
+ end interface ends_with
62
62
63
+ ! > Slices the input string to return a new string
63
64
! >
65
+ ! > Version: experimental
64
66
interface slice
65
67
module procedure :: slice_string
66
68
module procedure :: slice_char
@@ -298,31 +300,32 @@ elemental function ends_with_string_string(string, substring) result(match)
298
300
299
301
end function ends_with_string_string
300
302
301
- ! > Slices the region between first and last indexes of the input
302
- ! > string by taking strides of length stride
303
- elemental function slice_string (string , first , last , stride , include_last ) result(sliced_string)
303
+ ! > Slices the region between the input 'first' and 'last' index (both inclusive)
304
+ ! > of the input 'string' by taking strides of length 'stride'
305
+ ! > Returns a new string_type object
306
+ elemental function slice_string (string , first , last , stride ) result(sliced_string)
304
307
type (string_type), intent (in ) :: string
305
308
integer , intent (in ), optional :: first, last, stride
306
- logical , intent (in ), optional :: include_last
307
309
type (string_type) :: sliced_string
308
310
309
- sliced_string = string_type(slice(char (string), first, last, stride, include_last ))
311
+ sliced_string = string_type(slice(char (string), first, last, stride))
310
312
311
313
end function slice_string
312
314
313
- ! > Slices the region between first and last indexes of the input
314
- ! > character sequence by taking strides of length stride
315
- pure function slice_char (string , first , last , stride , include_last ) result(sliced_string)
315
+ ! > Slices the region between the input 'first' and 'last' index (both inclusive)
316
+ ! > of the input 'string' by taking strides of length 'stride'
317
+ ! > Returns a new string
318
+ pure function slice_char (string , first , last , stride ) result(sliced_string)
316
319
character (len=* ), intent (in ) :: string
317
320
integer , intent (in ), optional :: first, last, stride
318
- logical , intent (in ), optional :: include_last
319
321
integer :: first_index, last_index, stride_vector, n, i, j
320
322
character (len= :), allocatable :: sliced_string
321
323
322
- first_index = 1
323
- last_index = len (string)
324
- stride_vector = 1
325
324
if (len (string) > 0 ) then
325
+ first_index = 1
326
+ last_index = len (string)
327
+ stride_vector = 1
328
+
326
329
if (present (stride)) then
327
330
if (stride /= 0 ) then
328
331
if (stride < 0 ) then
@@ -348,20 +351,14 @@ pure function slice_char(string, first, last, stride, include_last) result(slice
348
351
349
352
n = int ((last_index - first_index) / stride_vector)
350
353
allocate (character (len= max (0 , n + 1 )) :: sliced_string)
351
-
352
- if (present (include_last)) then
353
- if (include_last) then
354
- first_index = last_index - (n * stride_vector)
355
- end if
356
- end if
357
354
358
355
j = 1
359
356
do i = first_index, last_index, stride_vector
360
357
sliced_string(j:j) = string (i:i)
361
358
j = j + 1
362
359
end do
363
360
else
364
- sliced_string = ' '
361
+ sliced_string = " "
365
362
end if
366
363
end function slice_char
367
364
0 commit comments