aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authormilancurcic <caomaco@gmail.com>2021-01-12 17:01:12 -0500
committermilancurcic <caomaco@gmail.com>2021-01-12 17:01:12 -0500
commit7af51a6a109099443164285fb97f8ca41e46ee3a (patch)
treec7dca050662c7e60400e474b3fe28927d1298de9
parentcf49f39f94c6da95842c8505117e7714ee016f41 (diff)
downloadfpm-7af51a6a109099443164285fb97f8ca41e46ee3a.tar.gz
fpm-7af51a6a109099443164285fb97f8ca41e46ee3a.zip
add function to replace characters in strings
-rw-r--r--fpm/src/fpm_strings.f9016
1 files changed, 15 insertions, 1 deletions
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index e3cee28..7d42d22 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -5,7 +5,7 @@ implicit none
private
public :: f_string, lower, split, str_ends_with, string_t
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
-public :: resize, str
+public :: replace, resize, str
type string_t
character(len=:), allocatable :: s
@@ -335,6 +335,20 @@ subroutine split(input_line,array,delimiters,order,nulls)
enddo
end subroutine split
+pure function replace(string, charset, target_char) result(res)
+ ! Returns string with characters in charset replaced with target_char.
+ character(*), intent(in) :: string
+ character, intent(in) :: charset(:), target_char
+ character(len(string)) :: res
+ integer :: n
+ res = string
+ do n = 1, len(string)
+ if (any(string(n:n) == charset)) then
+ res(n:n) = target_char
+ end if
+ end do
+end function replace
+
subroutine resize_string(list, n)
!> Instance of the array to be resized
type(string_t), allocatable, intent(inout) :: list(:)