Skip to content

Commit 798e229

Browse files
committed
added comments, improved compute_lps, changed default value of consider_overlapping
1 parent b49635b commit 798e229

File tree

1 file changed

+91
-38
lines changed

1 file changed

+91
-38
lines changed

src/stdlib_strings.f90

Lines changed: 91 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module stdlib_strings
88
use stdlib_string_type, only: string_type, char, verify
99
use stdlib_optval, only: optval
1010
implicit none
11-
private :: compute_LPS
11+
private :: compute_lps
1212

1313
public :: strip, chomp
1414
public :: starts_with, ends_with
@@ -376,73 +376,126 @@ pure function slice_char(string, first, last, stride) result(sliced_string)
376376
end do
377377
end function slice_char
378378

379+
!> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern'
380+
!> in input 'string'
381+
!> Returns an integer
382+
pure function find_string_string(string, pattern, occurrence, consider_overlapping) result(res)
383+
type(string_type), intent(in) :: string
384+
type(string_type), intent(in) :: pattern
385+
integer, intent(in), optional :: occurrence
386+
logical, intent(in), optional :: consider_overlapping
387+
integer :: res
388+
389+
res = find(char(string), char(pattern), occurrence, consider_overlapping)
390+
391+
end function find_string_string
392+
393+
!> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern'
394+
!> in input 'string'
395+
!> Returns an integer
396+
pure function find_string_char(string, pattern, occurrence, consider_overlapping) result(res)
397+
type(string_type), intent(in) :: string
398+
character(len=*), intent(in) :: pattern
399+
integer, intent(in), optional :: occurrence
400+
logical, intent(in), optional :: consider_overlapping
401+
integer :: res
402+
403+
res = find(char(string), pattern, occurrence, consider_overlapping)
404+
405+
end function find_string_char
406+
407+
!> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern'
408+
!> in input 'string'
409+
!> Returns an integer
410+
pure function find_char_string(string, pattern, occurrence, consider_overlapping) result(res)
411+
character(len=*), intent(in) :: string
412+
type(string_type), intent(in) :: pattern
413+
integer, intent(in), optional :: occurrence
414+
logical, intent(in), optional :: consider_overlapping
415+
integer :: res
416+
417+
res = find(string, char(pattern), occurrence, consider_overlapping)
418+
419+
end function find_char_string
420+
421+
!> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern'
422+
!> in input 'string'
423+
!> Returns an integer
379424
pure function find_char_char(string, pattern, occurrence, consider_overlapping) result(res)
380425
character(len=*), intent(in) :: string
381426
character(len=*), intent(in) :: pattern
382427
integer, intent(in), optional :: occurrence
383428
logical, intent(in), optional :: consider_overlapping
384-
integer :: LPS_array(len(pattern))
385-
integer :: res, i, j, length_string, length_pattern, occurrence_
429+
integer :: lps_array(len(pattern))
430+
integer :: res, s_i, p_i, length_string, length_pattern, occurrence_
386431
logical :: consider_overlapping_
387432

388-
consider_overlapping_ = optval(consider_overlapping, .false.)
389-
occurrence_ = max(1, optval(occurrence, 1))
390-
res = -1
433+
consider_overlapping_ = optval(consider_overlapping, .true.)
434+
occurrence_ = optval(occurrence, 1)
435+
res = 0
391436
length_string = len(string)
392437
length_pattern = len(pattern)
393438

394-
if (length_pattern > 0 .and. length_pattern <= length_string) then
395-
LPS_array = compute_LPS(pattern)
439+
if (length_pattern > 0 .and. length_pattern <= length_string &
440+
.and. occurrence_ > 0) then
441+
lps_array = compute_lps(pattern)
396442

397-
i = 1
398-
j = 1
399-
do while(i <= length_string)
400-
if (string(i:i) == pattern(j:j)) then
401-
if (j == length_pattern) then
443+
s_i = 1
444+
p_i = 1
445+
do while(s_i <= length_string)
446+
if (string(s_i:s_i) == pattern(p_i:p_i)) then
447+
if (p_i == length_pattern) then
402448
occurrence_ = occurrence_ - 1
403449
if (occurrence_ == 0) then
404-
res = i - length_pattern + 1
450+
res = s_i - length_pattern + 1
405451
exit
406452
else if (consider_overlapping_) then
407-
i = i - length_pattern + 1
453+
s_i = s_i - length_pattern + 1
408454
end if
409-
j = 0
455+
p_i = 0
410456
end if
411-
i = i + 1
412-
j = j + 1
413-
else if (j > 1) then
414-
j = LPS_array(j - 1) + 1
457+
s_i = s_i + 1
458+
p_i = p_i + 1
459+
else if (p_i > 1) then
460+
p_i = lps_array(p_i - 1) + 1
415461
else
416-
i = i + 1
462+
s_i = s_i + 1
417463
end if
418464
end do
419465
end if
420466

421467
end function find_char_char
422468

423-
pure function compute_LPS(string) result(LPS_array)
469+
!> Computes longest prefix suffix for each index of the input 'string'
470+
!>
471+
!> Returns an array of integers
472+
pure function compute_lps(string) result(lps_array)
424473
character(len=*), intent(in) :: string
425-
integer :: LPS_array(len(string))
474+
integer :: lps_array(len(string))
426475
integer :: i, j, length_string
427476

428477
length_string = len(string)
429-
LPS_array = 0
430478

431-
i = 2
432-
j = 1
433-
do while (i <= length_string)
434-
if (string(j:j) == string(i:i)) then
435-
LPS_array(i) = j
436-
i = i + 1
437-
j = j + 1
438-
else if (j > 1) then
439-
j = LPS_array(j - 1) + 1
440-
else
441-
i = i + 1
442-
end if
443-
end do
479+
if (length_string > 0) then
480+
lps_array(1) = 0
481+
482+
i = 2
483+
j = 1
484+
do while (i <= length_string)
485+
if (string(j:j) == string(i:i)) then
486+
lps_array(i) = j
487+
i = i + 1
488+
j = j + 1
489+
else if (j > 1) then
490+
j = lps_array(j - 1) + 1
491+
else
492+
lps_array(i) = 0
493+
i = i + 1
494+
end if
495+
end do
496+
end if
444497

445-
end function compute_LPS
498+
end function compute_lps
446499

447500

448501
end module stdlib_strings

0 commit comments

Comments
 (0)