Skip to content

Commit

Permalink
improved function slice for invalid cases, added new invalid test cases
Browse files Browse the repository at this point in the history
  • Loading branch information
aman-godara committed May 27, 2021
1 parent a733bc3 commit fa88905
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 28 deletions.
39 changes: 26 additions & 13 deletions src/stdlib_strings.f90
Original file line number Diff line number Diff line change
Expand Up @@ -318,18 +318,19 @@ end function slice_string
pure function slice_char(string, first, last, stride) result(sliced_string)
character(len=*), intent(in) :: string
integer, intent(in), optional :: first, last, stride
integer :: first_index, last_index, stride_vector, n, i, j
integer :: first_index, last_index, stride_vector, strides_taken, length_string, i, j
character(len=:), allocatable :: sliced_string

if (len(string) > 0) then
length_string = len(string)
if (length_string > 0) then
first_index = 1
last_index = len(string)
last_index = length_string
stride_vector = 1

if (present(stride)) then
if (stride /= 0) then
if (stride < 0) then
first_index = len(string)
first_index = length_string
last_index = 1
end if
stride_vector = stride
Expand All @@ -343,20 +344,32 @@ pure function slice_char(string, first, last, stride) result(sliced_string)
end if

if (present(first)) then
first_index = clip(first, 1, len(string))
first_index = first
end if
if (present(last)) then
last_index = clip(last, 1, len(string))
last_index = last
end if

n = int((last_index - first_index) / stride_vector)
allocate(character(len=max(0, n + 1)) :: sliced_string)
strides_taken = floor( real(last_index - first_index) / real(stride_vector) )

j = 1
do i = first_index, last_index, stride_vector
sliced_string(j:j) = string(i:i)
j = j + 1
end do
if (strides_taken < 0 .or. &
((first_index < 1 .and. last_index < 1) .or. &
(first_index > length_string .and. last_index > length_string))) then

sliced_string = ""
else
first_index = clip(first_index, 1, length_string)
last_index = clip(last_index, 1, length_string)

strides_taken = (last_index - first_index) / stride_vector
allocate(character(len=strides_taken + 1) :: sliced_string)

j = 1
do i = first_index, last_index, stride_vector
sliced_string(j:j) = string(i:i)
j = j + 1
end do
end if
else
sliced_string = ""
end if
Expand Down
42 changes: 27 additions & 15 deletions src/tests/string/test_string_functions.f90
Original file line number Diff line number Diff line change
Expand Up @@ -60,36 +60,48 @@ subroutine test_slice_string
test_char = "abcdefghijklmnopqrstuvwxyz"

call check(slice(test_string, 2, 16, 3) == "behkn", &
'function slice failed', warn=.true.)
call check(slice(test_char, 15, stride=-1) == "onmlkjihgfedcba", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, first=15, stride=-1) == "onmlkjihgfedcba", &
'function slice failed', warn=.false.)
call check(slice(test_string, last=22, stride=-1) == "zyxwv", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, 7, 2) == "gfedcb", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_string, 7, 2, 1) == "", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, 2, 6, -1) == "", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_string, stride=-1) == "zyxwvutsrqponmlkjihgfedcba", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_string, 7, 7, -4) == "g", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, 7, 7, 3) == "g", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_string, 7, 7, 3) == "g", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, 7, -10) == "gfedcba", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_string, 500, 22) == "zyxwv", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, 50, 27) == "", &
'function slice failed', warn=.false.)
call check(slice(test_string, -20, -200) == "", &
'function slice failed', warn=.false.)
call check(slice(test_char, first=0, stride=-1) == "", &
'function slice failed', warn=.false.)
call check(slice(test_string, last=27, stride=-2) == "", &
'function slice failed', warn=.false.)
call check(slice(test_char, first=27, stride=2) == "", &
'function slice failed', warn=.false.)
call check(slice(test_string, -500, 500) == "abcdefghijklmnopqrstuvwxyz", &
'function slice failed', warn=.false.)

test_string = ""
test_char = ""
call check(slice(test_string, 2, 16, 3) == "", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)
call check(slice(test_char, 2, 16, 3) == "", &
'function slice failed', warn=.true.)
'function slice failed', warn=.false.)

end subroutine test_slice_string

Expand Down

0 comments on commit fa88905

Please sign in to comment.