|
5 | 5 | !> The specification of this module is available [here](../page/specs/stdlib_strings.html).
|
6 | 6 | module stdlib_strings
|
7 | 7 | use stdlib_ascii, only: whitespace
|
8 |
| - use stdlib_string_type, only: string_type, char, verify, repeat, len |
| 8 | + use stdlib_string_type, only: string_type, char, verify, repeat, len, len_trim, move |
9 | 9 | use stdlib_optval, only: optval
|
10 |
| - use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool |
| 10 | + use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool, c_char |
| 11 | + use iso_c_binding, only: c_null_char |
11 | 12 | implicit none
|
12 | 13 | private
|
13 | 14 |
|
14 | 15 | public :: to_string
|
| 16 | + public :: to_c_char |
15 | 17 | public :: strip, chomp
|
16 | 18 | public :: starts_with, ends_with
|
17 |
| - public :: slice, find, replace_all, padl, padr, count, zfill |
| 19 | + public :: slice, find, replace_all, padl, padr, count, zfill, join |
18 | 20 |
|
19 | 21 | !> Version: experimental
|
20 | 22 | !>
|
@@ -43,6 +45,15 @@ module stdlib_strings
|
43 | 45 | #:endfor
|
44 | 46 | end interface to_string
|
45 | 47 |
|
| 48 | + !> Version: experimental |
| 49 | + !> |
| 50 | + !> Format or transfer other types as a string. |
| 51 | + !> ([Specification](../page/specs/stdlib_strings.html#to_c_char)) |
| 52 | + interface to_c_char |
| 53 | + module procedure to_c_char_from_char |
| 54 | + module procedure to_c_char_from_string |
| 55 | + end interface to_c_char |
| 56 | + |
46 | 57 | !> Remove leading and trailing whitespace characters.
|
47 | 58 | !>
|
48 | 59 | !> Version: experimental
|
@@ -164,6 +175,17 @@ module stdlib_strings
|
164 | 175 | module procedure :: zfill_char
|
165 | 176 | end interface zfill
|
166 | 177 |
|
| 178 | + !> Version: experimental |
| 179 | + !> |
| 180 | + !> Joins an array of strings into a single string. |
| 181 | + !> The chunks are separated with a space, or an optional user-defined separator. |
| 182 | + !> [Specifications](../page/specs/stdlib_strings.html#join) |
| 183 | + interface join |
| 184 | + module procedure :: join_string |
| 185 | + module procedure :: join_char |
| 186 | + end interface join |
| 187 | + |
| 188 | + |
167 | 189 | contains
|
168 | 190 |
|
169 | 191 |
|
@@ -943,5 +965,97 @@ contains
|
943 | 965 |
|
944 | 966 | end function zfill_char
|
945 | 967 |
|
| 968 | + !> Convert a Fortran character string to a C character array |
| 969 | + !> |
| 970 | + !> Version: experimental |
| 971 | + pure function to_c_char_from_char(value) result(cstr) |
| 972 | + character(len=*), intent(in) :: value |
| 973 | + character(kind=c_char) :: cstr(len(value)+1) |
| 974 | + integer :: i,lv |
| 975 | + lv = len(value) |
| 976 | + do concurrent (i=1:lv) |
| 977 | + cstr(i) = value(i:i) |
| 978 | + end do |
| 979 | + cstr(lv+1) = c_null_char |
| 980 | + end function to_c_char_from_char |
| 981 | + |
| 982 | + !> Convert a Fortran string type to a C character array |
| 983 | + !> |
| 984 | + !> Version: experimental |
| 985 | + pure function to_c_char_from_string(value) result(cstr) |
| 986 | + type(string_type), intent(in) :: value |
| 987 | + character(kind=c_char) :: cstr(len(value)+1) |
| 988 | + integer :: i,lv |
| 989 | + lv = len(value) |
| 990 | + do concurrent (i=1:lv) |
| 991 | + cstr(i) = char(value,pos=i) |
| 992 | + end do |
| 993 | + cstr(lv+1) = c_null_char |
| 994 | + end function to_c_char_from_string |
| 995 | + |
| 996 | + !> Joins a list of strings with a separator (default: space). |
| 997 | + !> Returns a new string |
| 998 | + pure type(string_type) function join_string(strings, separator) |
| 999 | + type(string_type), intent(in) :: strings(:) |
| 1000 | + character(len=*), intent(in), optional :: separator |
| 1001 | + integer :: ltot, i, lt, pos |
| 1002 | + character(len=:), allocatable :: sep,joined |
| 1003 | + ! Determine separator: use user-provided separator or default space |
| 1004 | + if (present(separator)) then |
| 1005 | + sep = separator |
| 1006 | + else |
| 1007 | + sep = ' ' |
| 1008 | + end if |
| 1009 | + ! Calculate the total length required, including separators |
| 1010 | + ltot = sum(len_trim(strings)) + (size(strings) - 1) * len(sep) |
| 1011 | + allocate(character(len=ltot) :: joined) |
| 1012 | + |
| 1013 | + ! Concatenate strings with separator |
| 1014 | + pos = 0 |
| 1015 | + do i = 1, size(strings) |
| 1016 | + lt = len_trim(strings(i)) |
| 1017 | + joined(pos+1:pos+lt) = char(strings(i),1,lt) |
| 1018 | + pos = pos + lt |
| 1019 | + if (i < size(strings)) then |
| 1020 | + joined(pos+1:pos+len(sep)) = sep |
| 1021 | + pos = pos + len(sep) |
| 1022 | + end if |
| 1023 | + end do |
| 1024 | + |
| 1025 | + call move(from=joined,to=join_string) |
| 1026 | + |
| 1027 | + end function join_string |
| 1028 | + |
| 1029 | + !> Joins a list of strings with a separator (default: space). |
| 1030 | + !> Returns a new string |
| 1031 | + pure function join_char(strings, separator) result(joined) |
| 1032 | + character(*), intent(in) :: strings(:) |
| 1033 | + character(len=*), intent(in), optional :: separator |
| 1034 | + character(len=:), allocatable :: joined |
| 1035 | + integer :: ltot, i, lt, pos |
| 1036 | + character(len=:), allocatable :: sep |
| 1037 | + ! Determine separator: use user-provided separator or default space |
| 1038 | + if (present(separator)) then |
| 1039 | + sep = separator |
| 1040 | + else |
| 1041 | + sep = ' ' |
| 1042 | + end if |
| 1043 | + ! Calculate the total length required, including separators |
| 1044 | + ltot = sum(len_trim(strings)) + (size(strings) - 1) * len(sep) |
| 1045 | + allocate(character(len=ltot) :: joined) |
| 1046 | + |
| 1047 | + joined = repeat(' ',ltot) |
| 1048 | + ! Concatenate strings with separator |
| 1049 | + pos = 0 |
| 1050 | + do i = 1, size(strings) |
| 1051 | + lt = len_trim(strings(i)) |
| 1052 | + joined(pos+1:pos+lt) = strings(i)(1:lt) |
| 1053 | + pos = pos + lt |
| 1054 | + if (i < size(strings)) then |
| 1055 | + joined(pos+1:pos+len(sep)) = sep |
| 1056 | + pos = pos + len(sep) |
| 1057 | + end if |
| 1058 | + end do |
| 1059 | + end function join_char |
946 | 1060 |
|
947 | 1061 | end module stdlib_strings
|
0 commit comments