Skip to content
58 changes: 56 additions & 2 deletions doc/specs/stdlib_strings.md
Original file line number Diff line number Diff line change
Expand Up @@ -283,7 +283,6 @@ Default value of `occurrence` is set to `1`.
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring as two different occurrences.
If `occurrence`th occurrence is not found, function returns `0`.


#### Syntax

`string = [[stdlib_strings(module):find(interface)]] (string, pattern [, occurrence, consider_overlapping])`
Expand Down Expand Up @@ -318,7 +317,7 @@ program demo_find
use stdlib_string_type, only: string_type, assignment(=)
use stdlib_strings, only : find
implicit none
string_type :: string
type(string_type) :: string

string = "needle in the character-stack"

Expand All @@ -328,3 +327,58 @@ program demo_find

end program demo_find
```


<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
### `replace_all`

#### Description

Replaces all occurrences of substring `pattern` in the input `string` with the replacement `replacement`.
Occurrences overlapping on a base occurrence will not be replaced.

#### Syntax

`string = [[stdlib_strings(module):replace_all(interface)]] (string, pattern, replacement)`

#### Status

Experimental

#### Class

Pure function

#### Argument

- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
This argument is intent(in).
- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
This argument is intent(in).
- `replacement`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
This argument is intent(in).

#### Result value

The result is of the same type as `string`.

#### Example

```fortran
program demo_replace_all
use stdlib_string_type, only: string_type, assignment(=)
use stdlib_strings, only : replace_all
implicit none
type(string_type) :: string

string = "hurdles here, hurdles there, hurdles everywhere"
! string <-- "hurdles here, hurdles there, hurdles everywhere"

print'(a)', replace_all(string, "hurdles", "learn from")
! "learn from here, learn from there, learn from everywhere"

string = replace_all(string, "hurdles", "technology")
! string <-- "technology here, technology there, technology everywhere"

end program demo_replace_all
```
153 changes: 151 additions & 2 deletions src/stdlib_strings.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module stdlib_strings

public :: strip, chomp
public :: starts_with, ends_with
public :: slice, find
public :: slice, find, replace_all


!> Remove leading and trailing whitespace characters.
Expand Down Expand Up @@ -79,6 +79,20 @@ module stdlib_strings
module procedure :: find_char_char
end interface find

!> Replaces all the occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Version: experimental
interface replace_all
module procedure :: replace_all_string_string_string
module procedure :: replace_all_string_string_char
module procedure :: replace_all_string_char_string
module procedure :: replace_all_char_string_string
module procedure :: replace_all_string_char_char
module procedure :: replace_all_char_string_char
module procedure :: replace_all_char_char_string
module procedure :: replace_all_char_char_char
end interface replace_all

contains


Expand Down Expand Up @@ -353,7 +367,7 @@ pure function slice_char(string, first, last, stride) result(sliced_string)
end if

if (present(first)) then
first_index = first
first_index = first
end if
if (present(last)) then
last_index = last
Expand Down Expand Up @@ -499,5 +513,140 @@ pure function compute_lps(string) result(lps_array)

end function compute_lps

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_string_string_string(string, pattern, replacement) result(res)
type(string_type), intent(in) :: string
type(string_type), intent(in) :: pattern
type(string_type), intent(in) :: replacement
type(string_type) :: res

res = string_type(replace_all(char(string), &
& char(pattern), char(replacement)))

end function replace_all_string_string_string

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_string_string_char(string, pattern, replacement) result(res)
type(string_type), intent(in) :: string
type(string_type), intent(in) :: pattern
character(len=*), intent(in) :: replacement
type(string_type) :: res

res = string_type(replace_all(char(string), char(pattern), replacement))

end function replace_all_string_string_char

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_string_char_string(string, pattern, replacement) result(res)
type(string_type), intent(in) :: string
character(len=*), intent(in) :: pattern
type(string_type), intent(in) :: replacement
type(string_type) :: res

res = string_type(replace_all(char(string), pattern, char(replacement)))

end function replace_all_string_char_string

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_char_string_string(string, pattern, replacement) result(res)
character(len=*), intent(in) :: string
type(string_type), intent(in) :: pattern
type(string_type), intent(in) :: replacement
character(len=:), allocatable :: res

res = replace_all(string, char(pattern), char(replacement))

end function replace_all_char_string_string

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_string_char_char(string, pattern, replacement) result(res)
type(string_type), intent(in) :: string
character(len=*), intent(in) :: pattern
character(len=*), intent(in) :: replacement
type(string_type) :: res

res = string_type(replace_all(char(string), pattern, replacement))

end function replace_all_string_char_char

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_char_string_char(string, pattern, replacement) result(res)
character(len=*), intent(in) :: string
type(string_type), intent(in) :: pattern
character(len=*), intent(in) :: replacement
character(len=:), allocatable :: res

res = replace_all(string, char(pattern), replacement)

end function replace_all_char_string_char

!> Replaces all occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_char_char_string(string, pattern, replacement) result(res)
character(len=*), intent(in) :: string
character(len=*), intent(in) :: pattern
type(string_type), intent(in) :: replacement
character(len=:), allocatable :: res

res = replace_all(string, pattern, char(replacement))

end function replace_all_char_char_string

!> Replaces all the occurrences of substring 'pattern' in the input 'string'
!> with the replacement 'replacement'
!> Returns a new string
pure function replace_all_char_char_char(string, pattern, replacement) result(res)
character(len=*), intent(in) :: string
character(len=*), intent(in) :: pattern
character(len=*), intent(in) :: replacement
character(len=:), allocatable :: res
integer :: lps_array(len(pattern))
integer :: s_i, p_i, last, length_string, length_pattern

res = ""
length_string = len(string)
length_pattern = len(pattern)
last = 1

if (length_pattern > 0 .and. length_pattern <= length_string) then
lps_array = compute_lps(pattern)

s_i = 1
p_i = 1
do while (s_i <= length_string)
if (string(s_i:s_i) == pattern(p_i:p_i)) then
if (p_i == length_pattern) then
res = res // &
& string(last : s_i - length_pattern) // &
& replacement
last = s_i + 1
p_i = 0
end if
s_i = s_i + 1
p_i = p_i + 1
else if (p_i > 1) then
p_i = lps_array(p_i - 1) + 1
else
s_i = s_i + 1
end if
end do
end if

res = res // string(last : length_string)

end function replace_all_char_char_char

end module stdlib_strings
Loading