aboutsummaryrefslogtreecommitdiff
path: root/src/fpm_strings.f90
diff options
context:
space:
mode:
Diffstat (limited to 'src/fpm_strings.f90')
-rw-r--r--src/fpm_strings.f9032
1 files changed, 32 insertions, 0 deletions
diff --git a/src/fpm_strings.f90 b/src/fpm_strings.f90
index efbf054..6ce36cf 100644
--- a/src/fpm_strings.f90
+++ b/src/fpm_strings.f90
@@ -31,6 +31,7 @@
module fpm_strings
use iso_fortran_env, only: int64
+use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer, c_size_t
implicit none
private
@@ -73,6 +74,10 @@ interface string_t
module procedure new_string_t
end interface string_t
+interface f_string
+ module procedure f_string, f_string_cptr, f_string_cptr_n
+end interface f_string
+
contains
!> test if a CHARACTER string ends with a specified suffix
@@ -128,6 +133,33 @@ function f_string(c_string)
end function f_string
+!> return Fortran character variable when given a null-terminated c_ptr
+function f_string_cptr(cptr) result(s)
+ type(c_ptr), intent(in), value :: cptr
+ character(len=:,kind=c_char), allocatable :: s
+
+ interface
+ function c_strlen(s) result(r) bind(c, name="strlen")
+ import c_size_t, c_ptr
+ type(c_ptr), intent(in), value :: s
+ integer(kind=c_size_t) :: r
+ end function
+ end interface
+
+ s = f_string_cptr_n(cptr, c_strlen(cptr))
+end function
+
+!> return Fortran character variable when given a null-terminated c_ptr and its length
+function f_string_cptr_n(cptr, n) result(s)
+ type(c_ptr), intent(in), value :: cptr
+ integer(kind=c_size_t), intent(in) :: n
+ character(len=n,kind=c_char) :: s
+ character(len=n,kind=c_char), pointer :: sptr
+
+ call c_f_pointer(cptr, sptr)
+ s = sptr
+end function
+
!> Hash a character(*) string of default kind
pure function fnv_1a_char(input, seed) result(hash)
character(*), intent(in) :: input