Skip to content

Commit 15827d2

Browse files
committed
shifted slice from stdlib_ascii to stdlib_strings and modified module dependencies accordingly
1 parent 1a5f78c commit 15827d2

File tree

3 files changed

+83
-61
lines changed

3 files changed

+83
-61
lines changed

src/Makefile.manual

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -56,9 +56,7 @@ $(SRCGEN): %.f90: %.fypp common.fypp
5656

5757
# Fortran module dependencies
5858
f18estop.o: stdlib_error.o
59-
stdlib_ascii.o: \
60-
stdlib_kinds.o \
61-
stdlib_math.o
59+
stdlib_ascii.o: stdlib_kinds.o
6260
stdlib_bitsets.o: stdlib_kinds.o
6361
stdlib_bitsets_64.o: stdlib_bitsets.o
6462
stdlib_bitsets_large.o: stdlib_bitsets.o
@@ -114,6 +112,9 @@ stdlib_stats_var.o: \
114112
stdlib_stats_distribution_PRNG.o: \
115113
stdlib_kinds.o \
116114
stdlib_error.o
117-
stdlib_string_type.o: stdlib_ascii.o stdlib_kinds.o
118-
stdlib_strings.o: stdlib_ascii.o stdlib_string_type.o
115+
stdlib_string_type.o: stdlib_ascii.o \
116+
stdlib_kinds.o
117+
stdlib_strings.o: stdlib_ascii.o \
118+
stdlib_string_type.o \
119+
stdlib_math.o
119120
stdlib_math.o: stdlib_kinds.o

src/stdlib_ascii.fypp

Lines changed: 1 addition & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@
66
!> The specification of this module is available [here](../page/specs/stdlib_ascii.html).
77
module stdlib_ascii
88
use stdlib_kinds, only : int8, int16, int32, int64
9-
use stdlib_math, only: clip
109

1110
implicit none
1211
private
@@ -21,7 +20,7 @@ module stdlib_ascii
2120

2221
! Character conversion functions
2322
public :: to_lower, to_upper, to_title, to_sentence, reverse
24-
public :: to_string, slice
23+
public :: to_string
2524

2625
!> Version: experimental
2726
!>
@@ -361,59 +360,6 @@ contains
361360

362361
end function reverse
363362

364-
pure function slice(string, first, last, stride, include_last) result(sliced_string)
365-
character(len=*), intent(in) :: string
366-
integer, intent(in), optional :: first, last, stride
367-
logical, intent(in), optional :: include_last
368-
integer :: first_index, last_index, stride_vector, n, i, j
369-
character(len=:), allocatable :: sliced_string
370-
371-
first_index = 1
372-
last_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-
first_index = len(string)
379-
last_index = 1
380-
end if
381-
stride_vector = stride
382-
end if
383-
else
384-
if (present(first) .and. present(last)) then
385-
if (last < first) then
386-
stride_vector = -1
387-
end if
388-
end if
389-
end if
390-
391-
if (present(first)) then
392-
first_index = clip(first, 1, len(string))
393-
end if
394-
if (present(last)) then
395-
last_index = clip(last, 1, len(string))
396-
end if
397-
398-
n = int((last_index - first_index) / stride_vector)
399-
allocate(character(len=max(0, n + 1)) :: sliced_string)
400-
401-
if (present(include_last)) then
402-
if (include_last) then
403-
first_index = last_index - (n * stride_vector)
404-
end if
405-
end if
406-
407-
j = 1
408-
do i = first_index, last_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-
417363
#:for kind in INT_KINDS
418364
!> Represent an integer of kind ${kind}$ as character sequence
419365
pure function to_string_integer_${kind}$(val) result(string)

src/stdlib_strings.f90

Lines changed: 76 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,11 +6,13 @@
66
module stdlib_strings
77
use stdlib_ascii, only : whitespace
88
use stdlib_string_type, only : string_type, char, verify
9+
use stdlib_math, only: clip
910
implicit none
1011
private
1112

1213
public :: strip, chomp
1314
public :: starts_with, ends_with
15+
public :: slice
1416

1517

1618
!> Remove leading and trailing whitespace characters.
@@ -56,7 +58,13 @@ module stdlib_strings
5658
module procedure :: ends_with_string_char
5759
module procedure :: ends_with_char_string
5860
module procedure :: ends_with_char_char
59-
end interface ends_with
61+
end interface
62+
63+
!>
64+
interface slice
65+
module procedure :: slice_string
66+
module procedure :: slice_char
67+
end interface slice
6068

6169

6270
contains
@@ -290,5 +298,72 @@ elemental function ends_with_string_string(string, substring) result(match)
290298

291299
end function ends_with_string_string
292300

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)
304+
type(string_type), intent(in) :: string
305+
integer, intent(in), optional :: first, last, stride
306+
logical, intent(in), optional :: include_last
307+
type(string_type) :: sliced_string
308+
309+
sliced_string = string_type(slice(char(string), first, last, stride, include_last))
310+
311+
end function slice_string
312+
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)
316+
character(len=*), intent(in) :: string
317+
integer, intent(in), optional :: first, last, stride
318+
logical, intent(in), optional :: include_last
319+
integer :: first_index, last_index, stride_vector, n, i, j
320+
character(len=:), allocatable :: sliced_string
321+
322+
first_index = 1
323+
last_index = len(string)
324+
stride_vector = 1
325+
if (len(string) > 0) then
326+
if (present(stride)) then
327+
if (stride /= 0) then
328+
if (stride < 0) then
329+
first_index = len(string)
330+
last_index = 1
331+
end if
332+
stride_vector = stride
333+
end if
334+
else
335+
if (present(first) .and. present(last)) then
336+
if (last < first) then
337+
stride_vector = -1
338+
end if
339+
end if
340+
end if
341+
342+
if (present(first)) then
343+
first_index = clip(first, 1, len(string))
344+
end if
345+
if (present(last)) then
346+
last_index = clip(last, 1, len(string))
347+
end if
348+
349+
n = int((last_index - first_index) / stride_vector)
350+
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+
358+
j = 1
359+
do i = first_index, last_index, stride_vector
360+
sliced_string(j:j) = string(i:i)
361+
j = j + 1
362+
end do
363+
else
364+
sliced_string = ''
365+
end if
366+
end function slice_char
367+
293368

294369
end module stdlib_strings

0 commit comments

Comments
 (0)