Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit 1fe2171

Browse files
authored
strings: join, to_c_char (#936)
2 parents bec8574 + 1f24d54 commit 1fe2171

File tree

8 files changed

+309
-10
lines changed

8 files changed

+309
-10
lines changed

‎doc/specs/stdlib_strings.md‎

Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -459,6 +459,43 @@ 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+
`joined = ` [[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(len=*)` 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/strings/example_join.f90!}
498+
```
462499

463500
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
464501
### `to_string`
@@ -498,3 +535,38 @@ The result is an `allocatable` length `character` scalar with up to `128` cached
498535
```fortran
499536
{!example/strings/example_to_string.f90!}
500537
```
538+
539+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
540+
### `to_c_char`
541+
542+
#### Description
543+
544+
Convert a Fortran `character` string or a `type(string_type)` variable to a C character array.
545+
This function converts a Fortran string into a C-style array of characters, ensuring proper null-termination for use in C functions or libraries.
546+
547+
#### Syntax
548+
549+
`cstr = ` [[stdlib_strings(module):to_c_char(function)]] ` (value)`
550+
551+
#### Status
552+
553+
Experimental
554+
555+
#### Class
556+
557+
Pure function.
558+
559+
#### Argument
560+
561+
- `value`: Shall be a `character(len=*)` string or a `type(string_type)` variable. It is an `intent(in)` argument.
562+
This Fortran variable will be converted to a C character array.
563+
564+
#### Result value
565+
566+
The result is a `character(kind=c_char)` array with a dimension of `len(value) + 1` to accommodate the null terminator.
567+
568+
#### Example
569+
570+
```fortran
571+
{!example/strings/example_to_c_char.f90!}
572+
```

‎example/strings/CMakeLists.txt‎

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,15 @@ ADD_EXAMPLE(chomp)
22
ADD_EXAMPLE(count)
33
ADD_EXAMPLE(ends_with)
44
ADD_EXAMPLE(find)
5+
ADD_EXAMPLE(join)
56
ADD_EXAMPLE(padl)
67
ADD_EXAMPLE(padr)
78
ADD_EXAMPLE(replace_all)
89
ADD_EXAMPLE(slice)
910
ADD_EXAMPLE(starts_with)
1011
ADD_EXAMPLE(strip)
1112
ADD_EXAMPLE(to_string)
13+
ADD_EXAMPLE(to_c_char)
1214
ADD_EXAMPLE(zfill)
1315
ADD_EXAMPLE(string_to_number)
14-
ADD_EXAMPLE(stream_of_strings_to_numbers)
16+
ADD_EXAMPLE(stream_of_strings_to_numbers)

‎example/strings/example_join.f90‎

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
program example_join
2+
use stdlib_strings, only: join
3+
implicit none
4+
5+
character(len=:), allocatable :: line
6+
character(*), parameter :: words(3) = [character(7) :: "Hello", "World", "Fortran"]
7+
8+
! Default separator (space)
9+
line = join(words)
10+
print *, "'" // line // "'" !! 'Hello World Fortran'
11+
12+
! Custom separator
13+
line = join(words, "_")
14+
print *, "'" // line // "'" !! 'Hello_World_Fortran'
15+
16+
! Custom 2-character separator
17+
line = join(words, ", ")
18+
print *, "'" // line // "'" !! 'Hello, World, Fortran'
19+
20+
end program example_join
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
program example_to_c_char
2+
use stdlib_strings, only: to_c_char
3+
use stdlib_string_type, only: string_type
4+
use stdlib_kinds, only: c_char
5+
implicit none
6+
7+
character(kind=c_char), allocatable :: cstr(:),cstr2(:)
8+
character(*), parameter :: hello = "Hello, World!"
9+
10+
! Convert character array
11+
cstr = to_c_char(hello)
12+
13+
! Convert string type
14+
cstr2 = to_c_char(string_type(hello))
15+
16+
if (size(cstr)/=size(cstr2) .or. .not.all(cstr==cstr2)) then
17+
error stop 'String conversion error'
18+
end if
19+
20+
end program example_to_c_char

‎src/stdlib_kinds.fypp‎

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,10 +4,10 @@
44
!> The specification of this module is available [here](../page/specs/stdlib_kinds.html).
55
module stdlib_kinds
66
use iso_fortran_env, only: int8, int16, int32, int64
7-
use iso_c_binding, only: c_bool
7+
use iso_c_binding, only: c_bool, c_char
88
implicit none
99
private
10-
public :: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool
10+
public :: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool, c_char
1111

1212
!> Single precision real numbers
1313
integer, parameter :: sp = selected_real_kind(6)

‎src/stdlib_strings.fypp‎

Lines changed: 117 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,16 +5,18 @@
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
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
1112
implicit none
1213
private
1314

1415
public :: to_string
16+
public :: to_c_char
1517
public :: strip, chomp
1618
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
1820

1921
!> Version: experimental
2022
!>
@@ -43,6 +45,15 @@ module stdlib_strings
4345
#:endfor
4446
end interface to_string
4547

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+
4657
!> Remove leading and trailing whitespace characters.
4758
!>
4859
!> Version: experimental
@@ -164,6 +175,17 @@ module stdlib_strings
164175
module procedure :: zfill_char
165176
end interface zfill
166177

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+
167189
contains
168190

169191

@@ -943,5 +965,97 @@ contains
943965

944966
end function zfill_char
945967

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
9461060

9471061
end module stdlib_strings

‎test/string/test_string_match.f90‎

Lines changed: 29 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
module test_string_match
33
use testdrive, only : new_unittest, unittest_type, error_type, check
44
use stdlib_ascii, only : reverse
5-
use stdlib_strings, only : starts_with, ends_with
5+
use stdlib_strings, only : starts_with, ends_with, join
66
use stdlib_string_type, only : string_type
77
implicit none
88

@@ -16,7 +16,8 @@ subroutine collect_string_match(testsuite)
1616

1717
testsuite = [ &
1818
new_unittest("starts_with", test_starts_with), &
19-
new_unittest("ends_with", test_ends_with) &
19+
new_unittest("ends_with", test_ends_with), &
20+
new_unittest("join", test_join) &
2021
]
2122
end subroutine collect_string_match
2223

@@ -77,6 +78,32 @@ subroutine check_ends_with(error, string, substring)
7778
call check(error, ends_with(string_type(string), string_type(substring)) .eqv. match, message)
7879
end subroutine check_ends_with
7980

81+
subroutine test_join(error)
82+
type(error_type), allocatable, intent(out) :: error
83+
character(len=5) :: test_strings(3)
84+
85+
test_strings = [character(5) :: "one", "two", "three"]
86+
call check_join(error, test_strings, " ", "one two three")
87+
if (allocated(error)) return
88+
call check_join(error, test_strings, ",", "one,two,three")
89+
if (allocated(error)) return
90+
call check_join(error, test_strings, "-", "one-two-three")
91+
end subroutine test_join
92+
93+
subroutine check_join(error, strings, separator, expected)
94+
type(error_type), allocatable, intent(out) :: error
95+
character(len=*), intent(in) :: strings(:)
96+
character(len=*), intent(in) :: separator
97+
character(len=*), intent(in) :: expected
98+
character(len=:), allocatable :: joined
99+
character(len=:), allocatable :: message
100+
101+
joined = join(strings, separator)
102+
message = "'join' error: Expected '" // expected // "' but got '" // joined // "'"
103+
call check(error, joined == expected, message)
104+
105+
end subroutine check_join
106+
80107
subroutine test_ends_with(error)
81108
type(error_type), allocatable, intent(out) :: error
82109
call check_ends_with(error, "pattern", "pat")

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /