Skip to content

Commit 4ed69eb

Browse files
authoredJul 4, 2021
Merge pull request #436 from Aman-Godara/replace_all
implemented low-level replace_all function
2 parents 9fb85ff + 7d38373 commit 4ed69eb

File tree

3 files changed

+320
-56
lines changed

3 files changed

+320
-56
lines changed
 

‎doc/specs/stdlib_strings.md

Lines changed: 56 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -283,7 +283,6 @@ Default value of `occurrence` is set to `1`.
283283
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring as two different occurrences.
284284
If `occurrence`th occurrence is not found, function returns `0`.
285285

286-
287286
#### Syntax
288287

289288
`string = [[stdlib_strings(module):find(interface)]] (string, pattern [, occurrence, consider_overlapping])`
@@ -318,7 +317,7 @@ program demo_find
318317
use stdlib_string_type, only: string_type, assignment(=)
319318
use stdlib_strings, only : find
320319
implicit none
321-
string_type :: string
320+
type(string_type) :: string
322321
323322
string = "needle in the character-stack"
324323
@@ -328,3 +327,58 @@ program demo_find
328327
329328
end program demo_find
330329
```
330+
331+
332+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
333+
### `replace_all`
334+
335+
#### Description
336+
337+
Replaces all occurrences of substring `pattern` in the input `string` with the replacement `replacement`.
338+
Occurrences overlapping on a base occurrence will not be replaced.
339+
340+
#### Syntax
341+
342+
`string = [[stdlib_strings(module):replace_all(interface)]] (string, pattern, replacement)`
343+
344+
#### Status
345+
346+
Experimental
347+
348+
#### Class
349+
350+
Pure function
351+
352+
#### Argument
353+
354+
- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
355+
This argument is intent(in).
356+
- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
357+
This argument is intent(in).
358+
- `replacement`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
359+
This argument is intent(in).
360+
361+
#### Result value
362+
363+
The result is of the same type as `string`.
364+
365+
#### Example
366+
367+
```fortran
368+
program demo_replace_all
369+
use stdlib_string_type, only: string_type, assignment(=)
370+
use stdlib_strings, only : replace_all
371+
implicit none
372+
type(string_type) :: string
373+
374+
string = "hurdles here, hurdles there, hurdles everywhere"
375+
! string <-- "hurdles here, hurdles there, hurdles everywhere"
376+
377+
print'(a)', replace_all(string, "hurdles", "learn from")
378+
! "learn from here, learn from there, learn from everywhere"
379+
380+
string = replace_all(string, "hurdles", "technology")
381+
! string <-- "technology here, technology there, technology everywhere"
382+
383+
end program demo_replace_all
384+
```

‎src/stdlib_strings.f90

Lines changed: 151 additions & 2 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
15+
public :: slice, find, replace_all
1616

1717

1818
!> Remove leading and trailing whitespace characters.
@@ -79,6 +79,20 @@ module stdlib_strings
7979
module procedure :: find_char_char
8080
end interface find
8181

82+
!> Replaces all the occurrences of substring 'pattern' in the input 'string'
83+
!> with the replacement 'replacement'
84+
!> Version: experimental
85+
interface replace_all
86+
module procedure :: replace_all_string_string_string
87+
module procedure :: replace_all_string_string_char
88+
module procedure :: replace_all_string_char_string
89+
module procedure :: replace_all_char_string_string
90+
module procedure :: replace_all_string_char_char
91+
module procedure :: replace_all_char_string_char
92+
module procedure :: replace_all_char_char_string
93+
module procedure :: replace_all_char_char_char
94+
end interface replace_all
95+
8296
contains
8397

8498

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

355369
if (present(first)) then
356-
first_index = first
370+
first_index = first
357371
end if
358372
if (present(last)) then
359373
last_index = last
@@ -499,5 +513,140 @@ pure function compute_lps(string) result(lps_array)
499513

500514
end function compute_lps
501515

516+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
517+
!> with the replacement 'replacement'
518+
!> Returns a new string
519+
pure function replace_all_string_string_string(string, pattern, replacement) result(res)
520+
type(string_type), intent(in) :: string
521+
type(string_type), intent(in) :: pattern
522+
type(string_type), intent(in) :: replacement
523+
type(string_type) :: res
524+
525+
res = string_type(replace_all(char(string), &
526+
& char(pattern), char(replacement)))
527+
528+
end function replace_all_string_string_string
529+
530+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
531+
!> with the replacement 'replacement'
532+
!> Returns a new string
533+
pure function replace_all_string_string_char(string, pattern, replacement) result(res)
534+
type(string_type), intent(in) :: string
535+
type(string_type), intent(in) :: pattern
536+
character(len=*), intent(in) :: replacement
537+
type(string_type) :: res
538+
539+
res = string_type(replace_all(char(string), char(pattern), replacement))
540+
541+
end function replace_all_string_string_char
542+
543+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
544+
!> with the replacement 'replacement'
545+
!> Returns a new string
546+
pure function replace_all_string_char_string(string, pattern, replacement) result(res)
547+
type(string_type), intent(in) :: string
548+
character(len=*), intent(in) :: pattern
549+
type(string_type), intent(in) :: replacement
550+
type(string_type) :: res
551+
552+
res = string_type(replace_all(char(string), pattern, char(replacement)))
553+
554+
end function replace_all_string_char_string
555+
556+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
557+
!> with the replacement 'replacement'
558+
!> Returns a new string
559+
pure function replace_all_char_string_string(string, pattern, replacement) result(res)
560+
character(len=*), intent(in) :: string
561+
type(string_type), intent(in) :: pattern
562+
type(string_type), intent(in) :: replacement
563+
character(len=:), allocatable :: res
564+
565+
res = replace_all(string, char(pattern), char(replacement))
566+
567+
end function replace_all_char_string_string
568+
569+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
570+
!> with the replacement 'replacement'
571+
!> Returns a new string
572+
pure function replace_all_string_char_char(string, pattern, replacement) result(res)
573+
type(string_type), intent(in) :: string
574+
character(len=*), intent(in) :: pattern
575+
character(len=*), intent(in) :: replacement
576+
type(string_type) :: res
577+
578+
res = string_type(replace_all(char(string), pattern, replacement))
579+
580+
end function replace_all_string_char_char
581+
582+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
583+
!> with the replacement 'replacement'
584+
!> Returns a new string
585+
pure function replace_all_char_string_char(string, pattern, replacement) result(res)
586+
character(len=*), intent(in) :: string
587+
type(string_type), intent(in) :: pattern
588+
character(len=*), intent(in) :: replacement
589+
character(len=:), allocatable :: res
590+
591+
res = replace_all(string, char(pattern), replacement)
592+
593+
end function replace_all_char_string_char
594+
595+
!> Replaces all occurrences of substring 'pattern' in the input 'string'
596+
!> with the replacement 'replacement'
597+
!> Returns a new string
598+
pure function replace_all_char_char_string(string, pattern, replacement) result(res)
599+
character(len=*), intent(in) :: string
600+
character(len=*), intent(in) :: pattern
601+
type(string_type), intent(in) :: replacement
602+
character(len=:), allocatable :: res
603+
604+
res = replace_all(string, pattern, char(replacement))
605+
606+
end function replace_all_char_char_string
607+
608+
!> Replaces all the occurrences of substring 'pattern' in the input 'string'
609+
!> with the replacement 'replacement'
610+
!> Returns a new string
611+
pure function replace_all_char_char_char(string, pattern, replacement) result(res)
612+
character(len=*), intent(in) :: string
613+
character(len=*), intent(in) :: pattern
614+
character(len=*), intent(in) :: replacement
615+
character(len=:), allocatable :: res
616+
integer :: lps_array(len(pattern))
617+
integer :: s_i, p_i, last, length_string, length_pattern
618+
619+
res = ""
620+
length_string = len(string)
621+
length_pattern = len(pattern)
622+
last = 1
623+
624+
if (length_pattern > 0 .and. length_pattern <= length_string) then
625+
lps_array = compute_lps(pattern)
626+
627+
s_i = 1
628+
p_i = 1
629+
do while (s_i <= length_string)
630+
if (string(s_i:s_i) == pattern(p_i:p_i)) then
631+
if (p_i == length_pattern) then
632+
res = res // &
633+
& string(last : s_i - length_pattern) // &
634+
& replacement
635+
last = s_i + 1
636+
p_i = 0
637+
end if
638+
s_i = s_i + 1
639+
p_i = p_i + 1
640+
else if (p_i > 1) then
641+
p_i = lps_array(p_i - 1) + 1
642+
else
643+
s_i = s_i + 1
644+
end if
645+
end do
646+
end if
647+
648+
res = res // string(last : length_string)
649+
650+
end function replace_all_char_char_char
502651

503652
end module stdlib_strings

‎src/tests/string/test_string_functions.f90

Lines changed: 113 additions & 52 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
7+
use stdlib_strings, only: slice, find, replace_all
88
use stdlib_optval, only: optval
99
use stdlib_ascii, only : to_string
1010
implicit none
@@ -63,102 +63,102 @@ subroutine test_slice_string
6363
! Only one argument is given
6464
! Valid
6565
call check(slice(test_string, first=10) == "jklmnopqrstuvwxyz", &
66-
"Slice, Valid arguments: first=10") ! last=+inf
66+
"slice, Valid arguments: first=10") ! last=+inf
6767
call check(slice(test_string, last=10) == "abcdefghij", &
68-
"Slice, Valid arguments: last=10") ! first=-inf
68+
"slice, Valid arguments: last=10") ! first=-inf
6969
call check(slice(test_string, stride=3) == "adgjmpsvy", &
70-
"Slice, Valid arguments: stride=3") ! first=-inf, last=+inf
70+
"slice, Valid arguments: stride=3") ! first=-inf, last=+inf
7171
call check(slice(test_string, stride=-3) == "zwtqnkheb", &
72-
"Slice, Valid arguments: stride=-3") ! first=+inf, last=-inf
72+
"slice, Valid arguments: stride=-3") ! first=+inf, last=-inf
7373

7474
! Invalid
7575
call check(slice(test_string, first=27) == "", &
76-
"Slice, Invalid arguments: first=27") ! last=+inf
76+
"slice, Invalid arguments: first=27") ! last=+inf
7777
call check(slice(test_string, first=-10) == "abcdefghijklmnopqrstuvwxyz", &
78-
"Slice, Invalid arguments: first=-10") ! last=+inf
78+
"slice, Invalid arguments: first=-10") ! last=+inf
7979
call check(slice(test_string, last=-2) == "", &
80-
"Slice, Invalid arguments: last=-2") ! first=-inf
80+
"slice, Invalid arguments: last=-2") ! first=-inf
8181
call check(slice(test_string, last=30) == "abcdefghijklmnopqrstuvwxyz", &
82-
"Slice, Invalid arguments: last=30") ! first=-inf
82+
"slice, Invalid arguments: last=30") ! first=-inf
8383
call check(slice(test_string, stride=0) == "abcdefghijklmnopqrstuvwxyz", &
84-
"Slice, Invalid arguments: stride=0") ! stride=1
84+
"slice, Invalid arguments: stride=0") ! stride=1
8585

8686
! Only two arguments are given
8787
! Valid
8888
call check(slice(test_string, first=10, last=20) == "jklmnopqrst", &
89-
"Slice, Valid arguments: first=10, last=20")
89+
"slice, Valid arguments: first=10, last=20")
9090
call check(slice(test_string, first=7, last=2) == "gfedcb", &
91-
"Slice, Valid arguments: first=7, last=2") ! stride=-1
91+
"slice, Valid arguments: first=7, last=2") ! stride=-1
9292
call check(slice(test_string, first=10, stride=-2) == "jhfdb", &
93-
"Slice, Valid arguments: first=10, stride=-2") ! last=-inf
93+
"slice, Valid arguments: first=10, stride=-2") ! last=-inf
9494
call check(slice(test_string, last=21, stride=-2) == "zxv", &
95-
"Slice, Valid arguments: last=21, stride=-2") ! first=+inf
95+
"slice, Valid arguments: last=21, stride=-2") ! first=+inf
9696

9797
! Atleast one argument is invalid
9898
call check(slice(test_string, first=30, last=-3) == "zyxwvutsrqponmlkjihgfedcba", &
99-
"Slice, Invalid arguments: first=30, last=-3")
99+
"slice, Invalid arguments: first=30, last=-3")
100100
call check(slice(test_string, first=1, last=-20) == "a", &
101-
"Slice, Invalid arguments: first=1, last=-20")
101+
"slice, Invalid arguments: first=1, last=-20")
102102
call check(slice(test_string, first=7, last=-10) == "gfedcba", &
103-
"Slice, Invalid arguments: first=7, last=-10")
103+
"slice, Invalid arguments: first=7, last=-10")
104104
call check(slice(test_string, first=500, last=22) == "zyxwv", &
105-
"Slice, Invalid arguments: first=500, last=22")
105+
"slice, Invalid arguments: first=500, last=22")
106106
call check(slice(test_string, first=50, last=27) == "", &
107-
"Slice, Invalid arguments: first=50, last=27")
107+
"slice, Invalid arguments: first=50, last=27")
108108
call check(slice(test_string, first=-20, last=0) == "", &
109-
"Slice, Invalid arguments: first=-20, last=0")
109+
"slice, Invalid arguments: first=-20, last=0")
110110
call check(slice(test_string, last=-3, stride=-2) == "zxvtrpnljhfdb", &
111-
"Slice, Invalid arguments: last=-3, stride=-2") ! first=+inf
111+
"slice, Invalid arguments: last=-3, stride=-2") ! first=+inf
112112
call check(slice(test_string, last=10, stride=0) == "abcdefghij", &
113-
"Slice, Invalid arguments: last=10, stride=0") ! stride=1
113+
"slice, Invalid arguments: last=10, stride=0") ! stride=1
114114
call check(slice(test_string, first=-2, stride=-2) == "", &
115-
"Slice, Invalid arguments: first=-2, stride=-2") ! last=-inf
115+
"slice, Invalid arguments: first=-2, stride=-2") ! last=-inf
116116
call check(slice(test_string, first=27, stride=2) == "", &
117-
"Slice, Invalid arguments: first=27, stride=2") ! last=+inf
117+
"slice, Invalid arguments: first=27, stride=2") ! last=+inf
118118
call check(slice(test_string, last=27, stride=-1) == "", &
119-
"Slice, Invalid arguments: last=27, stride=-1") ! first=+inf
119+
"slice, Invalid arguments: last=27, stride=-1") ! first=+inf
120120

121121
! All three arguments are given
122122
! Valid
123123
call check(slice(test_string, first=2, last=16, stride=3) == "behkn", &
124-
"Slice, Valid arguments: first=2, last=16, stride=3")
124+
"slice, Valid arguments: first=2, last=16, stride=3")
125125
call check(slice(test_string, first=16, last=2, stride=-3) == "pmjgd", &
126-
"Slice, Valid arguments: first=16, last=2, stride=-3")
126+
"slice, Valid arguments: first=16, last=2, stride=-3")
127127
call check(slice(test_string, first=7, last=7, stride=-4) == "g", &
128-
"Slice, Valid arguments: first=7, last=7, stride=-4")
128+
"slice, Valid arguments: first=7, last=7, stride=-4")
129129
call check(slice(test_string, first=7, last=7, stride=3) == "g", &
130-
"Slice, Valid arguments: first=7, last=7, stride=3")
130+
"slice, Valid arguments: first=7, last=7, stride=3")
131131
call check(slice(test_string, first=2, last=6, stride=-1) == "", &
132-
"Slice, Valid arguments: first=2, last=6, stride=-1")
132+
"slice, Valid arguments: first=2, last=6, stride=-1")
133133
call check(slice(test_string, first=20, last=10, stride=2) == "", &
134-
"Slice, Valid arguments: first=20, last=10, stride=2")
134+
"slice, Valid arguments: first=20, last=10, stride=2")
135135

136136
! Atleast one argument is invalid
137137
call check(slice(test_string, first=20, last=30, stride=2) == "tvxz", &
138-
"Slice, Invalid arguments: first=20, last=30, stride=2")
138+
"slice, Invalid arguments: first=20, last=30, stride=2")
139139
call check(slice(test_string, first=-20, last=30, stride=2) == "acegikmoqsuwy", &
140-
"Slice, Invalid arguments: first=-20, last=30, stride=2")
140+
"slice, Invalid arguments: first=-20, last=30, stride=2")
141141
call check(slice(test_string, first=26, last=30, stride=1) == "z", &
142-
"Slice, Invalid arguments: first=26, last=30, stride=1")
142+
"slice, Invalid arguments: first=26, last=30, stride=1")
143143
call check(slice(test_string, first=1, last=-20, stride=-1) == "a", &
144-
"Slice, Invalid arguments: first=1, last=-20, stride=-1")
144+
"slice, Invalid arguments: first=1, last=-20, stride=-1")
145145
call check(slice(test_string, first=26, last=20, stride=1) == "", &
146-
"Slice, Invalid arguments: first=26, last=20, stride=1")
146+
"slice, Invalid arguments: first=26, last=20, stride=1")
147147
call check(slice(test_string, first=1, last=20, stride=-1) == "", &
148-
"Slice, Invalid arguments: first=1, last=20, stride=-1")
148+
"slice, Invalid arguments: first=1, last=20, stride=-1")
149149

150150
test_string = ""
151151
! Empty string input
152152
call check(slice(test_string, first=-2, last=6) == "", &
153-
"Slice, Empty string: first=-2, last=6")
153+
"slice, Empty string: first=-2, last=6")
154154
call check(slice(test_string, first=6, last=-2) == "", &
155-
"Slice, Empty string: first=6, last=-2")
155+
"slice, Empty string: first=6, last=-2")
156156
call check(slice(test_string, first=-10) == "", &
157-
"Slice, Empty string: first=-10") ! last=+inf
157+
"slice, Empty string: first=-10") ! last=+inf
158158
call check(slice(test_string, last=10) == "", &
159-
"Slice, Empty string: last=10") ! first=-inf
159+
"slice, Empty string: last=10") ! first=-inf
160160
call check(slice(test_string) == "", &
161-
"Slice, Empty string: no arguments provided")
161+
"slice, Empty string: no arguments provided")
162162

163163
end subroutine test_slice_string
164164

@@ -170,27 +170,27 @@ subroutine test_find
170170
test_pattern_2 = "abccbabc"
171171

172172
call check(all(find([test_string_1, test_string_2], test_pattern_1, 4) == [7, 0]), &
173-
& 'Find: [test_string_1, test_string_2], test_pattern_1, 4')
173+
& 'find: [test_string_1, test_string_2], test_pattern_1, 4')
174174
call check(all(find(test_string_1, [test_pattern_1, test_pattern_2], 3, .false.) == [9, 0]), &
175-
& 'Find: test_string_1, [test_pattern_1, test_pattern_2], 3, .false.')
175+
& 'find: test_string_1, [test_pattern_1, test_pattern_2], 3, .false.')
176176
call check(find(test_string_1, test_pattern_1, 7) == 0, &
177-
& 'Find: test_string_1, test_pattern_1, 7')
177+
& 'find: test_string_1, test_pattern_1, 7')
178178
call check(all(find([test_string_1, test_string_2, test_string_2], [test_pattern_1, &
179179
& test_pattern_2, test_pattern_2], [7, 2, 2], [.true., .false., .true.]) == [0, 0, 6]), &
180-
& 'Find: [test_string_1, test_string_2, test_string_2], [test_pattern_1, &
180+
& 'find: [test_string_1, test_string_2, test_string_2], [test_pattern_1, &
181181
& test_pattern_2, test_pattern_2], [7, 2, 2], [.true., .false., .true.]')
182182
call check(find("qwqwqwqwqwqwqw", test_pattern_1) == 1, &
183-
& 'Find: "qwqwqwqwqwqwqw", test_pattern_1')
183+
& 'find: "qwqwqwqwqwqwqw", test_pattern_1')
184184
call check(all(find(test_string_1, ["qwq", "wqw"], 2) == [3, 4]), &
185-
& 'Find: test_string_1, ["qwq", "wqw"], 2')
185+
& 'find: test_string_1, ["qwq", "wqw"], 2')
186186
call check(find("qwqwqwqwqwqwqw", "qwq", 2, .false.) == 5, &
187-
& 'Find: "qwqwqwqwqwqwqw", "qwq", 2, .false.')
187+
& 'find: "qwqwqwqwqwqwqw", "qwq", 2, .false.')
188188
call check(find("", "") == 0, &
189-
& 'Find: "", ""')
189+
& 'find: "", ""')
190190
call check(find("", test_pattern_1) == 0, &
191-
& 'Find: "", test_pattern_1')
191+
& 'find: "", test_pattern_1')
192192
call check(find(test_string_1, "") == 0, &
193-
& 'Find: test_string_1, ""')
193+
& 'find: test_string_1, ""')
194194

195195
end subroutine test_find
196196

@@ -318,6 +318,66 @@ pure function carray_to_string(carray) result(string)
318318
string = transfer(carray, string)
319319
end function carray_to_string
320320

321+
subroutine test_replace_all
322+
type(string_type) :: test_string_1, test_pattern_1, test_replacement_1
323+
type(string_type) :: test_string_2, test_pattern_2, test_replacement_2
324+
test_string_1 = "mutate DNA sequence: GTTATCGTATGCCGTAATTAT"
325+
test_pattern_1 = "TAT"
326+
test_replacement_1 = "ATA"
327+
test_string_2 = "mutate DNA sequence: AGAGAGCCTAGAGAGAG"
328+
test_pattern_2 = "AGA"
329+
test_replacement_2 = "aga"
330+
331+
! all 3 as string_type
332+
call check(replace_all(test_string_1, test_pattern_1, test_replacement_1) == &
333+
& "mutate DNA sequence: GTATACGATAGCCGTAATATA", &
334+
& "replace_all: all 3 string_type, test case 1")
335+
call check(replace_all(test_string_2, test_pattern_2, test_replacement_2) == &
336+
& "mutate DNA sequence: agaGAGCCTagaGagaG", &
337+
& "replace_all: all 3 string_type, test case 2")
338+
call check(replace_all(test_string_2, test_pattern_2, test_replacement_1) == &
339+
& "mutate DNA sequence: ATAGAGCCTATAGATAG", &
340+
& "replace_all: all 3 string_type, test case 3")
341+
342+
! 2 as string_type and 1 as character scalar
343+
call check(replace_all(test_string_1, "tat", test_replacement_1) == &
344+
& "muATAe DNA sequence: GTTATCGTATGCCGTAATTAT", &
345+
& "replace_all: 2 string_type & 1 character scalar, test case 1")
346+
call check(replace_all(test_string_2, test_pattern_2, "GC") == &
347+
& "mutate DNA sequence: GCGAGCCTGCGGCG", &
348+
& "replace_all: 2 string_type & 1 character scalar, test case 2")
349+
call check(replace_all("mutate DNA sequence: AGAGAGCCTAGAGAGAG", test_pattern_2, &
350+
& test_replacement_2) == "mutate DNA sequence: agaGAGCCTagaGagaG", &
351+
& "replace_all: 2 string_type & 1 character scalar, test case 3")
352+
353+
354+
! 1 as string_type and 2 as character scalar
355+
call check(replace_all(test_string_1, "TAT", "ATA") == &
356+
& "mutate DNA sequence: GTATACGATAGCCGTAATATA", &
357+
& "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", &
360+
& "replace_all: 1 string_type & 2 character scalar, test case 2")
361+
call check(replace_all("mutate DNA sequence: GTTATCGTATGCCGTAATTAT", "TA", &
362+
& test_replacement_2) == "mutate DNA sequence: GTagaTCGagaTGCCGagaATagaT", &
363+
& "replace_all: 1 string_type & 2 character scalar, test case 3")
364+
call check(replace_all("mutate DNA sequence: GTTATCGTATGCCGTAATTAT", &
365+
& test_pattern_1, "") == "mutate DNA sequence: GTCGGCCGTAAT", &
366+
& "replace_all: 1 string_type & 2 character scalar, test case 4")
367+
call check(replace_all(test_string_1, "", "anything here") == test_string_1, &
368+
& "replace_all: 1 string_type & 2 character scalar, test case 5")
369+
call check(replace_all("", test_pattern_2, "anything here") == "", &
370+
& "replace_all: 1 string_type & 2 character scalar, test case 6")
371+
372+
! all 3 as character scalar
373+
call check(replace_all("mutate DNA sequence: GTTATCGTATGCCGTAATTAT", &
374+
& "GT", "gct") == "mutate DNA sequence: gctTATCgctATGCCgctAATTAT", &
375+
& "replace_all: all 3 character scalar, test case 1")
376+
call check(replace_all("", "anything here", "anything here") == "", &
377+
& "replace_all: all 3 character scalar, test case 2")
378+
379+
end subroutine test_replace_all
380+
321381
end module test_string_functions
322382

323383

@@ -333,5 +393,6 @@ program tester
333393
call test_slice_string
334394
call test_slice_gen
335395
call test_find
396+
call test_replace_all
336397

337398
end program tester

0 commit comments

Comments
 (0)
Please sign in to comment.