66!> The specification of this module is available [here](../page/specs/stdlib_ascii.html).
77module stdlib_ascii
88 use stdlib_kinds, only : int8, int16, int32, int64
9+ use stdlib_math, only: clip
910
1011 implicit none
1112 private
@@ -20,7 +21,7 @@ module stdlib_ascii
2021
2122 ! Character conversion functions
2223 public :: to_lower, to_upper, to_title, to_sentence, reverse
23- public :: to_string
24+ public :: to_string, slice
2425
2526 !> Version: experimental
2627 !>
@@ -360,6 +361,59 @@ contains
360361
361362 end function reverse
362363
364+ pure function slice(string, start, end, stride, include_end) result(sliced_string)
365+ character(len=*), intent(in) :: string
366+ integer, intent(in), optional :: start, end, stride
367+ logical, intent(in), optional :: include_end
368+ integer :: start_index, end_index, stride_vector, n, i, j
369+ character(len=:), allocatable :: sliced_string
370+
371+ start_index = 1
372+ end_index = len(string)
373+ stride_vector = 1
374+ if (len(string) > 0) then
375+ if (present(stride)) then
376+ if (stride /= 0) then
377+ if (stride < 0) then
378+ start_index = len(string)
379+ end_index = 1
380+ end if
381+ stride_vector = stride
382+ end if
383+ else
384+ if (present(start) .and. present(end)) then
385+ if (end < start) then
386+ stride_vector = -1
387+ end if
388+ end if
389+ end if
390+
391+ if (present(start)) then
392+ start_index = clip(start, 1, len(string))
393+ end if
394+ if (present(end)) then
395+ end_index = clip(end, 1, len(string))
396+ end if
397+
398+ n = int((end_index - start_index) / stride_vector)
399+ allocate(character(len=max(0, n + 1)) :: sliced_string)
400+
401+ if (present(include_end)) then
402+ if (include_end) then
403+ start_index = end_index - (n * stride_vector)
404+ end if
405+ end if
406+
407+ j = 1
408+ do i = start_index, end_index, stride_vector
409+ sliced_string(j:j) = string(i:i)
410+ j = j + 1
411+ end do
412+ else
413+ sliced_string = ''
414+ end if
415+ end function slice
416+
363417 #:for kind in INT_KINDS
364418 !> Represent an integer of kind ${kind}$ as character sequence
365419 pure function to_string_integer_${kind}$(val) result(string)
0 commit comments