Skip to content

Commit 7ed6fa0

Browse files
committed
Merge branch 'count' into pad
2 parents 7bc4b3a + c8fa8a5 commit 7ed6fa0

File tree

3 files changed

+194
-9
lines changed

3 files changed

+194
-9
lines changed

doc/specs/stdlib_strings.md

Lines changed: 54 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -280,7 +280,7 @@ end program demo_slice
280280
Returns the starting index of the `occurrence`th occurrence of the substring `pattern`
281281
in the input string `string`.
282282
Default value of `occurrence` is set to `1`.
283-
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring as two different occurrences.
283+
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring `pattern` as two different occurrences.
284284
If `occurrence`th occurrence is not found, function returns `0`.
285285

286286
#### Syntax
@@ -308,7 +308,7 @@ Elemental function
308308

309309
#### Result value
310310

311-
The result is a scalar of integer type or integer array of rank equal to the highest rank among all dummy arguments.
311+
The result is a scalar of integer type or an integer array of rank equal to the highest rank among all dummy arguments.
312312

313313
#### Example
314314

@@ -490,3 +490,55 @@ program demo_padr
490490
491491
end program demo_padr
492492
```
493+
494+
495+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
496+
### `count`
497+
498+
#### Description
499+
500+
Returns the number of times the substring `pattern` has occurred in the input string `string`.
501+
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring `pattern` as two different occurrences.
502+
503+
#### Syntax
504+
505+
`string = [[stdlib_strings(module):count(interface)]] (string, pattern [, consider_overlapping])`
506+
507+
#### Status
508+
509+
Experimental
510+
511+
#### Class
512+
513+
Elemental function
514+
515+
#### Argument
516+
517+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
518+
This argument is intent(in).
519+
- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
520+
This argument is intent(in).
521+
- `consider_overlapping`: logical.
522+
This argument is intent(in) and optional.
523+
524+
#### Result value
525+
526+
The result is a scalar of integer type or an integer array of rank equal to the highest rank among all dummy arguments.
527+
528+
#### Example
529+
530+
```fortran
531+
program demo_count
532+
use stdlib_string_type, only: string_type, assignment(=)
533+
use stdlib_strings, only : count
534+
implicit none
535+
type(string_type) :: string
536+
537+
string = "How much wood would a woodchuck chuck if a woodchuck could chuck wood?"
538+
539+
print *, count(string, "wood") ! 4
540+
print *, count(string, ["would", "chuck", "could"]) ! [1, 4, 1]
541+
print *, count("a long queueueueue", "ueu", [.false., .true.]) ! [2, 4]
542+
543+
end program demo_count
544+
```

src/stdlib_strings.f90

Lines changed: 94 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module stdlib_strings
1212

1313
public :: strip, chomp
1414
public :: starts_with, ends_with
15-
public :: slice, find, replace_all, padl, padr
15+
public :: slice, find, replace_all, padl, padr, count
1616

1717

1818
!> Remove leading and trailing whitespace characters.
@@ -113,6 +113,18 @@ module stdlib_strings
113113
module procedure :: padr_char_pad_with
114114
end interface padr
115115

116+
!> Version: experimental
117+
!>
118+
!> Returns the number of times substring 'pattern' has appeared in the
119+
!> input string 'string'
120+
!> [Specifications](../page/specs/stdlib_strings.html#count)
121+
interface count
122+
module procedure :: count_string_string
123+
module procedure :: count_string_char
124+
module procedure :: count_char_string
125+
module procedure :: count_char_char
126+
end interface count
127+
116128
contains
117129

118130

@@ -463,9 +475,7 @@ elemental function find_char_char(string, pattern, occurrence, consider_overlapp
463475
logical, intent(in), optional :: consider_overlapping
464476
integer :: lps_array(len(pattern))
465477
integer :: res, s_i, p_i, length_string, length_pattern, occurrence_
466-
logical :: consider_overlapping_
467478

468-
consider_overlapping_ = optval(consider_overlapping, .true.)
469479
occurrence_ = optval(occurrence, 1)
470480
res = 0
471481
length_string = len(string)
@@ -484,7 +494,7 @@ elemental function find_char_char(string, pattern, occurrence, consider_overlapp
484494
if (occurrence_ == 0) then
485495
res = s_i - length_pattern + 1
486496
exit
487-
else if (consider_overlapping_) then
497+
else if (optval(consider_overlapping, .true.)) then
488498
p_i = lps_array(p_i)
489499
else
490500
p_i = 0
@@ -786,5 +796,85 @@ pure function padr_char_pad_with(string, output_length, pad_with) result(res)
786796

787797
end function padr_char_pad_with
788798

799+
!> Returns the number of times substring 'pattern' has appeared in the
800+
!> input string 'string'
801+
!> Returns an integer
802+
elemental function count_string_string(string, pattern, consider_overlapping) result(res)
803+
type(string_type), intent(in) :: string
804+
type(string_type), intent(in) :: pattern
805+
logical, intent(in), optional :: consider_overlapping
806+
integer :: res
807+
808+
res = count(char(string), char(pattern), consider_overlapping)
809+
810+
end function count_string_string
811+
812+
!> Returns the number of times substring 'pattern' has appeared in the
813+
!> input string 'string'
814+
!> Returns an integer
815+
elemental function count_string_char(string, pattern, consider_overlapping) result(res)
816+
type(string_type), intent(in) :: string
817+
character(len=*), intent(in) :: pattern
818+
logical, intent(in), optional :: consider_overlapping
819+
integer :: res
820+
821+
res = count(char(string), pattern, consider_overlapping)
822+
823+
end function count_string_char
824+
825+
!> Returns the number of times substring 'pattern' has appeared in the
826+
!> input string 'string'
827+
!> Returns an integer
828+
elemental function count_char_string(string, pattern, consider_overlapping) result(res)
829+
character(len=*), intent(in) :: string
830+
type(string_type), intent(in) :: pattern
831+
logical, intent(in), optional :: consider_overlapping
832+
integer :: res
833+
834+
res = count(string, char(pattern), consider_overlapping)
835+
836+
end function count_char_string
837+
838+
!> Returns the number of times substring 'pattern' has appeared in the
839+
!> input string 'string'
840+
!> Returns an integer
841+
elemental function count_char_char(string, pattern, consider_overlapping) result(res)
842+
character(len=*), intent(in) :: string
843+
character(len=*), intent(in) :: pattern
844+
logical, intent(in), optional :: consider_overlapping
845+
integer :: lps_array(len(pattern))
846+
integer :: res, s_i, p_i, length_string, length_pattern
847+
848+
res = 0
849+
length_string = len(string)
850+
length_pattern = len(pattern)
851+
852+
if (length_pattern > 0 .and. length_pattern <= length_string) then
853+
lps_array = compute_lps(pattern)
854+
855+
s_i = 1
856+
p_i = 1
857+
do while (s_i <= length_string)
858+
if (string(s_i:s_i) == pattern(p_i:p_i)) then
859+
if (p_i == length_pattern) then
860+
res = res + 1
861+
if (optval(consider_overlapping, .true.)) then
862+
p_i = lps_array(p_i)
863+
else
864+
p_i = 0
865+
end if
866+
end if
867+
s_i = s_i + 1
868+
p_i = p_i + 1
869+
else if (p_i > 1) then
870+
p_i = lps_array(p_i - 1) + 1
871+
else
872+
s_i = s_i + 1
873+
end if
874+
end do
875+
end if
876+
877+
end function count_char_char
878+
789879

790880
end module stdlib_strings

src/tests/string/test_string_functions.f90

Lines changed: 46 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module test_string_functions
44
use stdlib_error, only : check
55
use stdlib_string_type, only : string_type, assignment(=), operator(==), &
66
to_lower, to_upper, to_title, to_sentence, reverse
7-
use stdlib_strings, only: slice, find, replace_all, padl, padr
7+
use stdlib_strings, only: slice, find, replace_all, padl, padr, count
88
use stdlib_optval, only: optval
99
use stdlib_ascii, only : to_string
1010
implicit none
@@ -355,8 +355,8 @@ subroutine test_replace_all
355355
call check(replace_all(test_string_1, "TAT", "ATA") == &
356356
& "mutate DNA sequence: GTATACGATAGCCGTAATATA", &
357357
& "replace_all: 1 string_type & 2 character scalar, test case 1")
358-
call check(replace_all("mutate DNA sequence: AGAGAGCCTAGAGAGAG", test_pattern_2, &
359-
& "GC") == "mutate DNA sequence: GCGAGCCTGCGGCG", &
358+
call check(replace_all("mutate DNA sequence: AGAGAGCCTAGAGAGAG", test_pattern_2, "GC") == &
359+
& "mutate DNA sequence: GCGAGCCTGCGGCG", &
360360
& "replace_all: 1 string_type & 2 character scalar, test case 2")
361361
call check(replace_all("mutate DNA sequence: GTTATCGTATGCCGTAATTAT", "TA", &
362362
& test_replacement_2) == "mutate DNA sequence: GTagaTCGagaTGCCGagaATagaT", &
@@ -452,6 +452,48 @@ subroutine test_padr
452452

453453
end subroutine test_padr
454454

455+
subroutine test_count
456+
type(string_type) :: test_string_1, test_string_2, test_pattern_1, test_pattern_2
457+
test_string_1 = "DNA sequence: AGAGAGAGTCCTGTCGAGA"
458+
test_string_2 = "DNA sequence: GTCCTGTCCTGTCAGA"
459+
test_pattern_1 = "AGA"
460+
test_pattern_2 = "GTCCTGTC"
461+
462+
! all 2 as string_type
463+
call check(all(count([test_string_1, test_string_2], test_pattern_1) == [4, 1]), &
464+
& 'count: all 2 as string_type, test case 1')
465+
call check(all(count(test_string_1, [test_pattern_1, test_pattern_2], .false.) == [3, 1]), &
466+
& 'count: all 2 as string_type, test case 2')
467+
call check(count(test_string_2, test_pattern_1, .false.) == 1, &
468+
& 'count: all 2 as string_type, test case 3')
469+
call check(all(count([test_string_2, test_string_2, test_string_1], &
470+
& [test_pattern_2, test_pattern_2, test_pattern_1], [.true., .false., .false.]) == &
471+
& [2, 1, 3]), 'count: all 2 as string_type, test case 4')
472+
call check(all(count([[test_string_1, test_string_2], [test_string_1, test_string_2]], &
473+
& [[test_pattern_1, test_pattern_2], [test_pattern_2, test_pattern_1]], .true.) == &
474+
& [[4, 2], [1, 1]]), 'count: all 2 as string_type, test case 5')
475+
476+
! 1 string_type and 1 character scalar
477+
call check(all(count(test_string_1, ["AGA", "GTC"], [.true., .false.]) == [4, 2]), &
478+
& 'count: 1 string_type and 1 character scalar, test case 1')
479+
call check(all(count([test_string_1, test_string_2], ["CTC", "GTC"], [.true., .false.]) == &
480+
& [0, 3]), 'count: 1 string_type and 1 character scalar, test case 2')
481+
call check(all(count(["AGAGAGAGTCCTGTCGAGA", "AGAGAGAGTCCTGTCGAGA"], &
482+
& test_pattern_1, [.false., .true.]) == [3, 4]), &
483+
& 'count: 1 string_type and 1 character scalar, test case 3')
484+
call check(count(test_string_1, "GAG") == 4, &
485+
& 'count: 1 string_type and 1 character scalar, test case 4')
486+
call check(count("DNA sequence: GTCCTGTCCTGTCAGA", test_pattern_2, .false.) == 1, &
487+
& 'count: 1 string_type and 1 character scalar, test case 5')
488+
489+
! all 2 character scalar
490+
call check(all(count("", ["mango", "trees"], .true.) == [0, 0]), &
491+
& 'count: all 2 character scalar, test case 1')
492+
call check(count("", "", .true.) == 0, 'count: all 2 character scalar, test case 2')
493+
call check(all(count(["mango", "trees"], "", .true.) == [0, 0]), &
494+
& 'count: all 2 character scalar, test case 3')
495+
496+
end subroutine test_count
455497

456498
end module test_string_functions
457499

@@ -471,5 +513,6 @@ program tester
471513
call test_replace_all
472514
call test_padl
473515
call test_padr
516+
call test_count
474517

475518
end program tester

0 commit comments

Comments
 (0)