@@ -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,17 @@ module stdlib_strings
9393 module procedure :: replace_all_char_char_char
9494 end interface replace_all
9595
96+ ! > Returns the number of times substring 'pattern' has appeared in the
97+ ! > input string 'string'
98+ ! > [Specifications](link to the specs - to be completed)
99+ ! > Version: experimental
100+ interface count
101+ module procedure :: count_string_string
102+ module procedure :: count_string_char
103+ module procedure :: count_char_string
104+ module procedure :: count_char_char
105+ end interface count
106+
96107contains
97108
98109
@@ -649,4 +660,87 @@ pure function replace_all_char_char_char(string, pattern, replacement) result(re
649660
650661 end function replace_all_char_char_char
651662
663+ ! > Returns the number of times substring 'pattern' has appeared in the
664+ ! > input string 'string'
665+ ! > Returns an integer
666+ elemental function count_string_string (string , pattern , consider_overlapping ) result(res)
667+ type (string_type), intent (in ) :: string
668+ type (string_type), intent (in ) :: pattern
669+ logical , intent (in ), optional :: consider_overlapping
670+ integer :: res
671+
672+ res = count (char (string), char (pattern), consider_overlapping)
673+
674+ end function count_string_string
675+
676+ ! > Returns the number of times substring 'pattern' has appeared in the
677+ ! > input string 'string'
678+ ! > Returns an integer
679+ elemental function count_string_char (string , pattern , consider_overlapping ) result(res)
680+ type (string_type), intent (in ) :: string
681+ character (len=* ), intent (in ) :: pattern
682+ logical , intent (in ), optional :: consider_overlapping
683+ integer :: res
684+
685+ res = count (char (string), pattern, consider_overlapping)
686+
687+ end function count_string_char
688+
689+ ! > Returns the number of times substring 'pattern' has appeared in the
690+ ! > input string 'string'
691+ ! > Returns an integer
692+ elemental function count_char_string (string , pattern , consider_overlapping ) result(res)
693+ character (len=* ), intent (in ) :: string
694+ type (string_type), intent (in ) :: pattern
695+ logical , intent (in ), optional :: consider_overlapping
696+ integer :: res
697+
698+ res = count (string, char (pattern), consider_overlapping)
699+
700+ end function count_char_string
701+
702+ ! > Returns the number of times substring 'pattern' has appeared in the
703+ ! > input string 'string'
704+ ! > Returns an integer
705+ elemental function count_char_char (string , pattern , consider_overlapping ) result(res)
706+ character (len=* ), intent (in ) :: string
707+ character (len=* ), intent (in ) :: pattern
708+ logical , intent (in ), optional :: consider_overlapping
709+ integer :: lps_array(len (pattern))
710+ integer :: res, s_i, p_i, length_string, length_pattern
711+ logical :: consider_overlapping_
712+
713+ consider_overlapping_ = optval(consider_overlapping, .true. )
714+ res = 0
715+ length_string = len (string)
716+ length_pattern = len (pattern)
717+
718+ if (length_pattern > 0 .and. length_pattern <= length_string) then
719+ lps_array = compute_lps(pattern)
720+
721+ s_i = 1
722+ p_i = 1
723+ do while (s_i <= length_string)
724+ if (string (s_i:s_i) == pattern(p_i:p_i)) then
725+ if (p_i == length_pattern) then
726+ res = res + 1
727+ if (consider_overlapping_) then
728+ p_i = lps_array(p_i)
729+ else
730+ p_i = 0
731+ end if
732+ end if
733+ s_i = s_i + 1
734+ p_i = p_i + 1
735+ else if (p_i > 1 ) then
736+ p_i = lps_array(p_i - 1 ) + 1
737+ else
738+ s_i = s_i + 1
739+ end if
740+ end do
741+ end if
742+
743+ end function count_char_char
744+
745+
652746end module stdlib_strings
0 commit comments