Skip to content

Commit c7c1e48

Browse files
committed
removed include_last functionality
1 parent 15827d2 commit c7c1e48

File tree

1 file changed

+17
-20
lines changed

1 file changed

+17
-20
lines changed

src/stdlib_strings.f90

Lines changed: 17 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -58,9 +58,11 @@ module stdlib_strings
5858
module procedure :: ends_with_string_char
5959
module procedure :: ends_with_char_string
6060
module procedure :: ends_with_char_char
61-
end interface
61+
end interface ends_with
6262

63+
!> Slices the input string to return a new string
6364
!>
65+
!> Version: experimental
6466
interface slice
6567
module procedure :: slice_string
6668
module procedure :: slice_char
@@ -298,31 +300,32 @@ elemental function ends_with_string_string(string, substring) result(match)
298300

299301
end function ends_with_string_string
300302

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)
304307
type(string_type), intent(in) :: string
305308
integer, intent(in), optional :: first, last, stride
306-
logical, intent(in), optional :: include_last
307309
type(string_type) :: sliced_string
308310

309-
sliced_string = string_type(slice(char(string), first, last, stride, include_last))
311+
sliced_string = string_type(slice(char(string), first, last, stride))
310312

311313
end function slice_string
312314

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)
316319
character(len=*), intent(in) :: string
317320
integer, intent(in), optional :: first, last, stride
318-
logical, intent(in), optional :: include_last
319321
integer :: first_index, last_index, stride_vector, n, i, j
320322
character(len=:), allocatable :: sliced_string
321323

322-
first_index = 1
323-
last_index = len(string)
324-
stride_vector = 1
325324
if (len(string) > 0) then
325+
first_index = 1
326+
last_index = len(string)
327+
stride_vector = 1
328+
326329
if (present(stride)) then
327330
if (stride /= 0) then
328331
if (stride < 0) then
@@ -348,20 +351,14 @@ pure function slice_char(string, first, last, stride, include_last) result(slice
348351

349352
n = int((last_index - first_index) / stride_vector)
350353
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
357354

358355
j = 1
359356
do i = first_index, last_index, stride_vector
360357
sliced_string(j:j) = string(i:i)
361358
j = j + 1
362359
end do
363360
else
364-
sliced_string = ''
361+
sliced_string = ""
365362
end if
366363
end function slice_char
367364

0 commit comments

Comments
 (0)