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
10
use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool
11
11
use iso_c_binding, only: c_char, c_null_char
@@ -16,7 +16,7 @@ module stdlib_strings
16
16
public :: to_c_string
17
17
public :: strip, chomp
18
18
public :: starts_with, ends_with
19
- public :: slice, find, replace_all, padl, padr, count, zfill
19
+ public :: slice, find, replace_all, padl, padr, count, zfill, join
20
20
21
21
!> Version: experimental
22
22
!>
@@ -166,6 +166,16 @@ module stdlib_strings
166
166
module procedure :: zfill_char
167
167
end interface zfill
168
168
169
+ !> Version: experimental
170
+ !>
171
+ !> Joins an array of strings into a single string.
172
+ !> The chunks are separated with a space, or an optional user-defined separator.
173
+ !> [Specifications](../page/specs/stdlib_strings.html#join)
174
+ interface join
175
+ module procedure :: join_string
176
+ module procedure :: join_char
177
+ end interface join
178
+
169
179
contains
170
180
171
181
@@ -958,4 +968,77 @@ contains
958
968
cstr(len(value)+1) = c_null_char
959
969
end function to_c_string
960
970
971
+ !> Joins a list of strings with a separator (default: space).
972
+ !> Returns a new string
973
+ pure function join_string(strings, separator) result(cmd)
974
+ type(string_type), intent(in) :: strings(:)
975
+ character(len=*), intent(in), optional :: separator
976
+ type(string_type) :: cmd
977
+
978
+ integer :: ltot, i, lt, pos
979
+ character(len=:), allocatable :: sep,cmd_char
980
+
981
+ ! Determine separator: use user-provided separator or default space
982
+ if (present(separator)) then
983
+ sep = separator
984
+ else
985
+ sep = ' '
986
+ end if
987
+
988
+ ! Calculate the total length required, including separators
989
+ ltot = sum(len_trim(strings)) + (size(strings) - 1) * len(sep)
990
+ allocate(character(len=ltot) :: cmd_char)
991
+
992
+ ! Concatenate strings with separator
993
+ pos = 0
994
+ do i = 1, size(strings)
995
+ lt = len_trim(strings(i))
996
+ cmd_char(pos+1:pos+lt) = char(strings(i),1,lt)
997
+ pos = pos + lt
998
+ if (i < size(strings)) then
999
+ cmd_char(pos+1:pos+len(sep)) = sep
1000
+ pos = pos + len(sep)
1001
+ end if
1002
+ end do
1003
+
1004
+ call move(from=cmd_char,to=cmd)
1005
+
1006
+ end function join_string
1007
+
1008
+ !> Joins a list of strings with a separator (default: space).
1009
+ !> Returns a new string
1010
+ pure function join_char(strings, separator) result(cmd)
1011
+ character(*), intent(in) :: strings(:)
1012
+ character(len=*), intent(in), optional :: separator
1013
+ character(:), allocatable :: cmd
1014
+
1015
+ integer :: ltot, i, lt, pos
1016
+ character(len=:), allocatable :: sep
1017
+
1018
+ ! Determine separator: use user-provided separator or default space
1019
+ if (present(separator)) then
1020
+ sep = separator
1021
+ else
1022
+ sep = ' '
1023
+ end if
1024
+
1025
+ ! Calculate the total length required, including separators
1026
+ ltot = sum(len_trim(strings)) + (size(strings) - 1) * len(sep)
1027
+ allocate(character(len=ltot) :: cmd)
1028
+
1029
+ cmd = repeat(' ',ltot)
1030
+
1031
+ ! Concatenate strings with separator
1032
+ pos = 0
1033
+ do i = 1, size(strings)
1034
+ lt = len_trim(strings(i))
1035
+ cmd(pos+1:pos+lt) = strings(i)(1:lt)
1036
+ pos = pos + lt
1037
+ if (i < size(strings)) then
1038
+ cmd(pos+1:pos+len(sep)) = sep
1039
+ pos = pos + len(sep)
1040
+ end if
1041
+ end do
1042
+ end function join_char
1043
+
961
1044
end module stdlib_strings
0 commit comments