Skip to content

Commit d2ac7ae

Browse files
authored
implemented intelligent slice functionality (#414)
implemented intelligent slice functionality
2 parents 9929cdb + d38e0f4 commit d2ac7ae

File tree

5 files changed

+396
-4
lines changed

5 files changed

+396
-4
lines changed

doc/specs/stdlib_string_type.md

+2-2
Original file line numberDiff line numberDiff line change
@@ -1254,7 +1254,7 @@ The result is a scalar `string_type` value.
12541254

12551255
```fortran
12561256
program demo_to_title
1257-
use stdlib_string_type, only: string_type, to_title
1257+
use stdlib_string_type
12581258
implicit none
12591259
type(string_type) :: string, titlecase_string
12601260
@@ -1302,7 +1302,7 @@ The result is a scalar `string_type` value.
13021302

13031303
```fortran
13041304
program demo_to_sentence
1305-
use stdlib_string_type, only: string_type, to_sentence
1305+
use stdlib_string_type
13061306
implicit none
13071307
type(string_type) :: string, sentencecase_string
13081308

doc/specs/stdlib_strings.md

+78
Original file line numberDiff line numberDiff line change
@@ -192,3 +192,81 @@ program demo
192192
print'(a)', ends_with("pattern", "pat") ! F
193193
end program demo
194194
```
195+
196+
197+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
198+
### `slice`
199+
200+
#### Description
201+
202+
Extracts the characters from the defined region of the input string by taking strides.
203+
204+
Deduction Process:
205+
Function first automatically deduces the optional arguments that are not provided by the user.
206+
This process is independent of both input `string` and permitted indexes of Fortran.
207+
Deduced `first` and `last` argument take +infinity or -infinity value whereas deduced `stride` argument takes +1 or -1 value.
208+
209+
Validation Process:
210+
Argument `first` and `last` defines this region for extraction by function `slice`.
211+
If the defined region is invalid i.e. region contains atleast one invalid index, `first` and
212+
`last` are converted to first and last valid indexes in this defined region respectively,
213+
if no valid index exists in this region an empty string is returned.
214+
`stride` can attain both negative or positive values but when the only invalid value
215+
0 is given, it is converted to 1.
216+
217+
Extraction Process:
218+
After all this, extraction starts from `first` index and takes stride of length `stride`.
219+
Extraction starts only if `last` index is crossable from `first` index with stride `stride`
220+
and remains active until `last` index is crossed.
221+
222+
#### Syntax
223+
224+
`string = [[stdlib_strings(module):slice(interface)]] (string, first, last, stride)`
225+
226+
#### Status
227+
228+
Experimental
229+
230+
#### Class
231+
232+
Pure function.
233+
234+
#### Argument
235+
236+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]]
237+
This argument is intent(in).
238+
- `first`: integer
239+
This argument is intent(in) and optional.
240+
- `last`: integer
241+
This argument is intent(in) and optional.
242+
- `stride`: integer
243+
This argument is intent(in) and optional.
244+
245+
#### Result value
246+
247+
The result is of the same type as `string`.
248+
249+
#### Example
250+
251+
```fortran
252+
program demo_slice
253+
use stdlib_string_type
254+
use stdlib_strings, only : slice
255+
implicit none
256+
type(string_type) :: string
257+
character(len=10) :: char
258+
259+
string = "abcdefghij"
260+
! string <-- "abcdefghij"
261+
262+
char = "abcdefghij"
263+
! char <-- "abcdefghij"
264+
265+
print'(a)', slice("abcdefghij", 2, 6, 2) ! "bdf"
266+
print'(a)', slice(char, 2, 6, 2) ! "bdf"
267+
268+
string = slice(string, 2, 6, 2)
269+
! string <-- "bdf"
270+
271+
end program demo_slice
272+
```

src/Makefile.manual

+4-2
Original file line numberDiff line numberDiff line change
@@ -125,6 +125,8 @@ stdlib_stats_var.o: \
125125
stdlib_stats_distribution_PRNG.o: \
126126
stdlib_kinds.o \
127127
stdlib_error.o
128-
stdlib_string_type.o: stdlib_ascii.o stdlib_kinds.o
129-
stdlib_strings.o: stdlib_ascii.o stdlib_string_type.o
128+
stdlib_string_type.o: stdlib_ascii.o \
129+
stdlib_kinds.o
130+
stdlib_strings.o: stdlib_ascii.o \
131+
stdlib_string_type.o
130132
stdlib_math.o: stdlib_kinds.o

src/stdlib_strings.f90

+76
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module stdlib_strings
1111

1212
public :: strip, chomp
1313
public :: starts_with, ends_with
14+
public :: slice
1415

1516

1617
!> Remove leading and trailing whitespace characters.
@@ -57,6 +58,14 @@ module stdlib_strings
5758
module procedure :: ends_with_char_string
5859
module procedure :: ends_with_char_char
5960
end interface ends_with
61+
62+
!> Extracts characters from the input string to return a new string
63+
!>
64+
!> Version: experimental
65+
interface slice
66+
module procedure :: slice_string
67+
module procedure :: slice_char
68+
end interface slice
6069

6170

6271
contains
@@ -290,5 +299,72 @@ elemental function ends_with_string_string(string, substring) result(match)
290299

291300
end function ends_with_string_string
292301

302+
!> Extract the characters from the region between 'first' and 'last' index (both inclusive)
303+
!> of the input 'string' by taking strides of length 'stride'
304+
!> Returns a new string
305+
elemental function slice_string(string, first, last, stride) result(sliced_string)
306+
type(string_type), intent(in) :: string
307+
integer, intent(in), optional :: first, last, stride
308+
type(string_type) :: sliced_string
309+
310+
sliced_string = string_type(slice(char(string), first, last, stride))
311+
312+
end function slice_string
313+
314+
!> Extract the characters from the region between 'first' and 'last' index (both inclusive)
315+
!> of the input 'string' by taking strides of length 'stride'
316+
!> Returns a new string
317+
pure function slice_char(string, first, last, stride) result(sliced_string)
318+
character(len=*), intent(in) :: string
319+
integer, intent(in), optional :: first, last, stride
320+
integer :: first_index, last_index, stride_vector, strides_taken, length_string, i, j
321+
character(len=:), allocatable :: sliced_string
322+
length_string = len(string)
323+
324+
first_index = 0 ! first_index = -infinity
325+
last_index = length_string + 1 ! last_index = +infinity
326+
stride_vector = 1
327+
328+
if (present(stride)) then
329+
if (stride /= 0) then
330+
if (stride < 0) then
331+
first_index = length_string + 1 ! first_index = +infinity
332+
last_index = 0 ! last_index = -infinity
333+
end if
334+
stride_vector = stride
335+
end if
336+
else
337+
if (present(first) .and. present(last)) then
338+
if (last < first) then
339+
stride_vector = -1
340+
end if
341+
end if
342+
end if
343+
344+
if (present(first)) then
345+
first_index = first
346+
end if
347+
if (present(last)) then
348+
last_index = last
349+
end if
350+
351+
if (stride_vector > 0) then
352+
first_index = max(first_index, 1)
353+
last_index = min(last_index, length_string)
354+
else
355+
first_index = min(first_index, length_string)
356+
last_index = max(last_index, 1)
357+
end if
358+
359+
strides_taken = floor( real(last_index - first_index)/real(stride_vector) )
360+
allocate(character(len=max(0, strides_taken + 1)) :: sliced_string)
361+
362+
j = 1
363+
do i = first_index, last_index, stride_vector
364+
sliced_string(j:j) = string(i:i)
365+
j = j + 1
366+
end do
367+
end function slice_char
368+
293369

294370
end module stdlib_strings

0 commit comments

Comments
 (0)