Skip to content

Commit 81f028a

Browse files
committed
Testing against intrinsic array slice access
1 parent fa88905 commit 81f028a

File tree

1 file changed

+128
-0
lines changed

1 file changed

+128
-0
lines changed

src/tests/string/test_string_functions.f90

+128
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,12 @@
11
! SPDX-Identifier: MIT
22
module test_string_functions
3+
use, intrinsic :: iso_fortran_env, only : error_unit
34
use stdlib_error, only : check
45
use stdlib_string_type, only : string_type, assignment(=), operator(==), &
56
to_lower, to_upper, to_title, to_sentence, reverse
67
use stdlib_strings, only: slice
8+
use stdlib_optval, only: optval
9+
use stdlib_ascii, only : to_string
710
implicit none
811

912
contains
@@ -105,6 +108,130 @@ subroutine test_slice_string
105108

106109
end subroutine test_slice_string
107110

111+
subroutine test_slice_gen
112+
character(len=*), parameter :: test = &
113+
& "abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789"
114+
integer :: i, j, k
115+
integer, parameter :: offset = 3
116+
117+
do i = 1 - offset, len(test) + offset
118+
call check_slicer(test, first=i)
119+
end do
120+
121+
do i = 1 - offset, len(test) + offset
122+
call check_slicer(test, last=i)
123+
end do
124+
125+
do i = -len(test) - offset, len(test) + offset
126+
call check_slicer(test, stride=i)
127+
end do
128+
129+
do i = 1 - offset, len(test) + offset
130+
do j = 1 - offset, len(test) + offset
131+
call check_slicer(test, first=i, last=j)
132+
end do
133+
end do
134+
135+
do i = 1 - offset, len(test) + offset
136+
do j = -len(test) - offset, len(test) + offset
137+
call check_slicer(test, first=i, stride=j)
138+
end do
139+
end do
140+
141+
do i = 1 - offset, len(test) + offset
142+
do j = -len(test) - offset, len(test) + offset
143+
call check_slicer(test, last=i, stride=j)
144+
end do
145+
end do
146+
147+
do i = 1 - offset, len(test) + offset
148+
do j = 1 - offset, len(test) + offset
149+
do k = -len(test) - offset, len(test) + offset
150+
call check_slicer(test, first=i, last=j, stride=k)
151+
end do
152+
end do
153+
end do
154+
end subroutine test_slice_gen
155+
156+
subroutine check_slicer(string, first, last, stride)
157+
character(len=*), intent(in) :: string
158+
integer, intent(in), optional :: first
159+
integer, intent(in), optional :: last
160+
integer, intent(in), optional :: stride
161+
162+
character(len=:), allocatable :: actual, expected, message
163+
logical :: stat
164+
165+
actual = slice(string, first, last, stride)
166+
expected = reference_slice(string, first, last, stride)
167+
168+
stat = actual == expected
169+
170+
if (.not.stat) then
171+
message = "For input '"//string//"'"//new_line('a')
172+
173+
if (present(first)) then
174+
message = message // "first: "//to_string(first)//new_line('a')
175+
end if
176+
if (present(last)) then
177+
message = message // "last: "//to_string(last)//new_line('a')
178+
end if
179+
if (present(stride)) then
180+
message = message // "stride: "//to_string(stride)//new_line('a')
181+
end if
182+
message = message // "Expected: '"//expected//"' but got '"//actual//"'"
183+
end if
184+
call check(stat, message)
185+
186+
end subroutine check_slicer
187+
188+
pure function reference_slice(string, first, last, stride) result(sliced_string)
189+
character(len=*), intent(in) :: string
190+
integer, intent(in), optional :: first
191+
integer, intent(in), optional :: last
192+
integer, intent(in), optional :: stride
193+
character(len=:), allocatable :: sliced_string
194+
character(len=1), allocatable :: carray(:)
195+
196+
integer :: first_, last_, stride_
197+
198+
stride_ = 1
199+
if (present(stride)) then
200+
stride_ = merge(stride_, stride, stride == 0)
201+
else
202+
if (present(first) .and. present(last)) then
203+
if (last < first) stride_ = -1
204+
end if
205+
end if
206+
207+
if (stride_ < 0) then
208+
last_ = min(max(optval(last, 1), 1), len(string)+1)
209+
first_ = min(max(optval(first, len(string)), 0), len(string))
210+
else
211+
first_ = min(max(optval(first, 1), 1), len(string)+1)
212+
last_ = min(max(optval(last, len(string)), 0), len(string))
213+
end if
214+
215+
carray = string_to_carray(string)
216+
carray = carray(first_:last_:stride_)
217+
sliced_string = carray_to_string(carray)
218+
219+
end function reference_slice
220+
221+
pure function string_to_carray(string) result(carray)
222+
character(len=*), intent(in) :: string
223+
character(len=1) :: carray(len(string))
224+
225+
carray = transfer(string, carray)
226+
end function string_to_carray
227+
228+
pure function carray_to_string(carray) result(string)
229+
character(len=1), intent(in) :: carray(:)
230+
character(len=size(carray)) :: string
231+
232+
string = transfer(carray, string)
233+
end function carray_to_string
234+
108235
end module test_string_functions
109236

110237

@@ -118,5 +245,6 @@ program tester
118245
call test_to_sentence_string
119246
call test_reverse_string
120247
call test_slice_string
248+
call test_slice_gen
121249

122250
end program tester

0 commit comments

Comments
 (0)