aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm_strings.f9093
1 files changed, 92 insertions, 1 deletions
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index 8e57d5b..ad0a843 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -5,7 +5,9 @@ implicit none
private
public :: f_string, lower, split, str_ends_with, string_t
public :: string_array_contains, string_cat, operator(.in.), fnv_1a
-public :: resize
+public :: resize, str
+
+integer, parameter :: dp = selected_real_kind(15)
type string_t
character(len=:), allocatable :: s
@@ -29,6 +31,10 @@ interface str_ends_with
procedure :: str_ends_with_any
end interface str_ends_with
+interface str
+ module procedure str_int, str_int64, str_real, str_real_n, str_logical
+end interface
+
contains
pure logical function str_ends_with_str(s, e) result(r)
@@ -349,4 +355,89 @@ subroutine resize_string(list, n)
end subroutine resize_string
+pure integer function str_int_len(i) result(sz)
+! Returns the length of the string representation of 'i'
+integer, intent(in) :: i
+integer, parameter :: MAX_STR = 100
+character(MAX_STR) :: s
+! If 's' is too short (MAX_STR too small), Fortran will abort with:
+! "Fortran runtime error: End of record"
+write(s, '(i0)') i
+sz = len_trim(s)
+end function
+
+pure function str_int(i) result(s)
+! Converts integer "i" to string
+integer, intent(in) :: i
+character(len=str_int_len(i)) :: s
+write(s, '(i0)') i
+end function
+
+pure integer function str_int64_len(i) result(sz)
+! Returns the length of the string representation of 'i'
+integer(int64), intent(in) :: i
+integer, parameter :: MAX_STR = 100
+character(MAX_STR) :: s
+! If 's' is too short (MAX_STR too small), Fortran will abort with:
+! "Fortran runtime error: End of record"
+write(s, '(i0)') i
+sz = len_trim(s)
+end function
+
+pure function str_int64(i) result(s)
+! Converts integer "i" to string
+integer(int64), intent(in) :: i
+character(len=str_int64_len(i)) :: s
+write(s, '(i0)') i
+end function
+
+pure integer function str_real_len(r, fmt) result(sz)
+! Returns the length of the string representation of 'i'
+real(dp), intent(in) :: r
+character(len=*), intent(in) :: fmt
+integer, parameter :: MAX_STR = 100
+character(MAX_STR) :: s
+! If 's' is too short (MAX_STR too small), Fortan will abort with:
+! "Fortran runtime error: End of record"
+write(s, fmt) r
+sz = len_trim(s)
+end function
+
+pure function str_real(r) result(s)
+! Converts the real number "r" to string with 7 decimal digits.
+real(dp), intent(in) :: r
+character(len=*), parameter :: fmt="(f0.6)"
+character(len=str_real_len(r, fmt)) :: s
+write(s, fmt) r
+end function
+
+pure function str_real_n(r, n) result(s)
+! Converts the real number "r" to string with 'n' decimal digits.
+real(dp), intent(in) :: r
+integer, intent(in) :: n
+character(len=str_real_len(r, "(f0." // str_int(n) // ")")) :: s
+write(s, "(f0." // str_int(n) // ")") r
+end function
+
+pure integer function str_logical_len(l) result(sz)
+! Returns the length of the string representation of 'l'
+logical, intent(in) :: l
+if (l) then
+ sz = 6
+else
+ sz = 7
+end if
+end function
+
+pure function str_logical(l) result(s)
+! Converts logical "l" to string
+logical, intent(in) :: l
+character(len=str_logical_len(l)) :: s
+if (l) then
+ s = ".true."
+else
+ s = ".false."
+end if
+end function
+
end module fpm_strings