Skip to content

Commit 519d53d

Browse files
committed
implement join
1 parent 5b543a2 commit 519d53d

File tree

2 files changed

+129
-2
lines changed

2 files changed

+129
-2
lines changed

doc/specs/stdlib_strings.md

Lines changed: 44 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -459,8 +459,52 @@ The result is of the same type as `string`.
459459
{!example/strings/example_zfill.f90!}
460460
```
461461

462+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
463+
### `join`
464+
465+
#### Description
466+
467+
Joins an array of strings into a single string. This function concatenates the strings from the input array,
468+
inserting a separator between each string (default: space). A user-defined separator may be provided, The resulting string is returned.
469+
470+
471+
#### Syntax
472+
473+
`cmd = ` [[stdlib_strings(module):join(interface)]] ` (strings, separator)`
474+
475+
#### Status
476+
477+
Experimental
478+
479+
#### Class
480+
481+
Pure function
482+
483+
#### Argument
484+
485+
- `strings`: Array of strings (either `type(string_type)` or `character(len=*)`).
486+
This argument is `intent(in)`. It is an array of strings that will be concatenated together.
487+
- `separator`: Character scalar (optional).
488+
This argument is `intent(in)`. It specifies the separator to be used between the strings. If not provided, the default separator (a space) is used.
489+
490+
#### Result value
491+
492+
The result is of the same type as the elements of `strings` (`type(string_type)` or `character(len=:), allocatable`).
493+
494+
#### Example
495+
496+
```fortran
497+
! Example usage:
498+
program test_join
499+
type(string_type) :: result
500+
type(string_type), dimension(3) :: words = [string_type('hello'), string_type('world'), string_type('fortran')]
501+
result = join_string(words, ', ') ! Joins with comma and space
502+
print *, result ! Output: "hello, world, fortran"
503+
end program test_join
504+
```
462505

463506
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
507+
464508
### `to_string`
465509

466510
#### Description

src/stdlib_strings.fypp

Lines changed: 85 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
!> The specification of this module is available [here](../page/specs/stdlib_strings.html).
66
module stdlib_strings
77
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
99
use stdlib_optval, only: optval
1010
use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool
1111
use iso_c_binding, only: c_char, c_null_char
@@ -16,7 +16,7 @@ module stdlib_strings
1616
public :: to_c_string
1717
public :: strip, chomp
1818
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
2020

2121
!> Version: experimental
2222
!>
@@ -166,6 +166,16 @@ module stdlib_strings
166166
module procedure :: zfill_char
167167
end interface zfill
168168

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+
169179
contains
170180

171181

@@ -958,4 +968,77 @@ contains
958968
cstr(len(value)+1) = c_null_char
959969
end function to_c_string
960970

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+
9611044
end module stdlib_strings

0 commit comments

Comments
 (0)