Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit c2b8338

Browse files
authored
Merge pull request #453 from Aman-Godara/count
implemented count function
2 parents b555c27 + c8fa8a5 commit c2b8338

File tree

3 files changed

+197
-10
lines changed

3 files changed

+197
-10
lines changed

‎doc/specs/stdlib_strings.md

Lines changed: 55 additions & 3 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

@@ -381,4 +381,56 @@ program demo_replace_all
381381
! string <-- "technology here, technology there, technology everywhere"
382382
383383
end program demo_replace_all
384-
```
384+
```
385+
386+
387+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
388+
### `count`
389+
390+
#### Description
391+
392+
Returns the number of times the substring `pattern` has occurred in the input string `string`.
393+
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring `pattern` as two different occurrences.
394+
395+
#### Syntax
396+
397+
`string = [[stdlib_strings(module):count(interface)]] (string, pattern [, consider_overlapping])`
398+
399+
#### Status
400+
401+
Experimental
402+
403+
#### Class
404+
405+
Elemental function
406+
407+
#### Argument
408+
409+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
410+
This argument is intent(in).
411+
- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
412+
This argument is intent(in).
413+
- `consider_overlapping`: logical.
414+
This argument is intent(in) and optional.
415+
416+
#### Result value
417+
418+
The result is a scalar of integer type or an integer array of rank equal to the highest rank among all dummy arguments.
419+
420+
#### Example
421+
422+
```fortran
423+
program demo_count
424+
use stdlib_string_type, only: string_type, assignment(=)
425+
use stdlib_strings, only : count
426+
implicit none
427+
type(string_type) :: string
428+
429+
string = "How much wood would a woodchuck chuck if a woodchuck could chuck wood?"
430+
431+
print *, count(string, "wood") ! 4
432+
print *, count(string, ["would", "chuck", "could"]) ! [1, 4, 1]
433+
print *, count("a long queueueueue", "ueu", [.false., .true.]) ! [2, 4]
434+
435+
end program demo_count
436+
```

‎src/stdlib_strings.f90

Lines changed: 95 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
15+
public :: slice, find, replace_all, count
1616

1717

1818
!> Remove leading and trailing whitespace characters.
@@ -93,6 +93,18 @@ module stdlib_strings
9393
module procedure :: replace_all_char_char_char
9494
end interface replace_all
9595

96+
!> Version: experimental
97+
!>
98+
!> Returns the number of times substring 'pattern' has appeared in the
99+
!> input string 'string'
100+
!> [Specifications](../page/specs/stdlib_strings.html#count)
101+
interface count
102+
module procedure :: count_string_string
103+
module procedure :: count_string_char
104+
module procedure :: count_char_string
105+
module procedure :: count_char_char
106+
end interface count
107+
96108
contains
97109

98110

@@ -443,9 +455,7 @@ elemental function find_char_char(string, pattern, occurrence, consider_overlapp
443455
logical, intent(in), optional :: consider_overlapping
444456
integer :: lps_array(len(pattern))
445457
integer :: res, s_i, p_i, length_string, length_pattern, occurrence_
446-
logical :: consider_overlapping_
447458

448-
consider_overlapping_ = optval(consider_overlapping, .true.)
449459
occurrence_ = optval(occurrence, 1)
450460
res = 0
451461
length_string = len(string)
@@ -464,7 +474,7 @@ elemental function find_char_char(string, pattern, occurrence, consider_overlapp
464474
if (occurrence_ == 0) then
465475
res = s_i - length_pattern + 1
466476
exit
467-
else if (consider_overlapping_) then
477+
else if (optval(consider_overlapping, .true.)) then
468478
p_i = lps_array(p_i)
469479
else
470480
p_i = 0
@@ -649,4 +659,85 @@ pure function replace_all_char_char_char(string, pattern, replacement) result(re
649659

650660
end function replace_all_char_char_char
651661

662+
!> Returns the number of times substring 'pattern' has appeared in the
663+
!> input string 'string'
664+
!> Returns an integer
665+
elemental function count_string_string(string, pattern, consider_overlapping) result(res)
666+
type(string_type), intent(in) :: string
667+
type(string_type), intent(in) :: pattern
668+
logical, intent(in), optional :: consider_overlapping
669+
integer :: res
670+
671+
res = count(char(string), char(pattern), consider_overlapping)
672+
673+
end function count_string_string
674+
675+
!> Returns the number of times substring 'pattern' has appeared in the
676+
!> input string 'string'
677+
!> Returns an integer
678+
elemental function count_string_char(string, pattern, consider_overlapping) result(res)
679+
type(string_type), intent(in) :: string
680+
character(len=*), intent(in) :: pattern
681+
logical, intent(in), optional :: consider_overlapping
682+
integer :: res
683+
684+
res = count(char(string), pattern, consider_overlapping)
685+
686+
end function count_string_char
687+
688+
!> Returns the number of times substring 'pattern' has appeared in the
689+
!> input string 'string'
690+
!> Returns an integer
691+
elemental function count_char_string(string, pattern, consider_overlapping) result(res)
692+
character(len=*), intent(in) :: string
693+
type(string_type), intent(in) :: pattern
694+
logical, intent(in), optional :: consider_overlapping
695+
integer :: res
696+
697+
res = count(string, char(pattern), consider_overlapping)
698+
699+
end function count_char_string
700+
701+
!> Returns the number of times substring 'pattern' has appeared in the
702+
!> input string 'string'
703+
!> Returns an integer
704+
elemental function count_char_char(string, pattern, consider_overlapping) result(res)
705+
character(len=*), intent(in) :: string
706+
character(len=*), intent(in) :: pattern
707+
logical, intent(in), optional :: consider_overlapping
708+
integer :: lps_array(len(pattern))
709+
integer :: res, s_i, p_i, length_string, length_pattern
710+
711+
res = 0
712+
length_string = len(string)
713+
length_pattern = len(pattern)
714+
715+
if (length_pattern > 0 .and. length_pattern <= length_string) then
716+
lps_array = compute_lps(pattern)
717+
718+
s_i = 1
719+
p_i = 1
720+
do while (s_i <= length_string)
721+
if (string(s_i:s_i) == pattern(p_i:p_i)) then
722+
if (p_i == length_pattern) then
723+
res = res + 1
724+
if (optval(consider_overlapping, .true.)) then
725+
p_i = lps_array(p_i)
726+
else
727+
p_i = 0
728+
end if
729+
end if
730+
s_i = s_i + 1
731+
p_i = p_i + 1
732+
else if (p_i > 1) then
733+
p_i = lps_array(p_i - 1) + 1
734+
else
735+
s_i = s_i + 1
736+
end if
737+
end do
738+
end if
739+
740+
end function count_char_char
741+
742+
652743
end module stdlib_strings

‎src/tests/string/test_string_functions.f90

Lines changed: 47 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
7+
use stdlib_strings, only: slice, find, replace_all, 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", &
@@ -378,6 +378,49 @@ subroutine test_replace_all
378378

379379
end subroutine test_replace_all
380380

381+
subroutine test_count
382+
type(string_type) :: test_string_1, test_string_2, test_pattern_1, test_pattern_2
383+
test_string_1 = "DNA sequence: AGAGAGAGTCCTGTCGAGA"
384+
test_string_2 = "DNA sequence: GTCCTGTCCTGTCAGA"
385+
test_pattern_1 = "AGA"
386+
test_pattern_2 = "GTCCTGTC"
387+
388+
! all 2 as string_type
389+
call check(all(count([test_string_1, test_string_2], test_pattern_1) == [4, 1]), &
390+
& 'count: all 2 as string_type, test case 1')
391+
call check(all(count(test_string_1, [test_pattern_1, test_pattern_2], .false.) == [3, 1]), &
392+
& 'count: all 2 as string_type, test case 2')
393+
call check(count(test_string_2, test_pattern_1, .false.) == 1, &
394+
& 'count: all 2 as string_type, test case 3')
395+
call check(all(count([test_string_2, test_string_2, test_string_1], &
396+
& [test_pattern_2, test_pattern_2, test_pattern_1], [.true., .false., .false.]) == &
397+
& [2, 1, 3]), 'count: all 2 as string_type, test case 4')
398+
call check(all(count([[test_string_1, test_string_2], [test_string_1, test_string_2]], &
399+
& [[test_pattern_1, test_pattern_2], [test_pattern_2, test_pattern_1]], .true.) == &
400+
& [[4, 2], [1, 1]]), 'count: all 2 as string_type, test case 5')
401+
402+
! 1 string_type and 1 character scalar
403+
call check(all(count(test_string_1, ["AGA", "GTC"], [.true., .false.]) == [4, 2]), &
404+
& 'count: 1 string_type and 1 character scalar, test case 1')
405+
call check(all(count([test_string_1, test_string_2], ["CTC", "GTC"], [.true., .false.]) == &
406+
& [0, 3]), 'count: 1 string_type and 1 character scalar, test case 2')
407+
call check(all(count(["AGAGAGAGTCCTGTCGAGA", "AGAGAGAGTCCTGTCGAGA"], &
408+
& test_pattern_1, [.false., .true.]) == [3, 4]), &
409+
& 'count: 1 string_type and 1 character scalar, test case 3')
410+
call check(count(test_string_1, "GAG") == 4, &
411+
& 'count: 1 string_type and 1 character scalar, test case 4')
412+
call check(count("DNA sequence: GTCCTGTCCTGTCAGA", test_pattern_2, .false.) == 1, &
413+
& 'count: 1 string_type and 1 character scalar, test case 5')
414+
415+
! all 2 character scalar
416+
call check(all(count("", ["mango", "trees"], .true.) == [0, 0]), &
417+
& 'count: all 2 character scalar, test case 1')
418+
call check(count("", "", .true.) == 0, 'count: all 2 character scalar, test case 2')
419+
call check(all(count(["mango", "trees"], "", .true.) == [0, 0]), &
420+
& 'count: all 2 character scalar, test case 3')
421+
422+
end subroutine test_count
423+
381424
end module test_string_functions
382425

383426

@@ -394,5 +437,6 @@ program tester
394437
call test_slice_gen
395438
call test_find
396439
call test_replace_all
440+
call test_count
397441

398442
end program tester

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /