diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index 099aa5521..970800d4c 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -459,6 +459,43 @@ The result is of the same type as `string`. {!example/strings/example_zfill.f90!} ``` + +### `join` + +#### Description + +Joins an array of strings into a single string. This function concatenates the strings from the input array, +inserting a separator between each string (default: space). A user-defined separator may be provided, The resulting string is returned. + + +#### Syntax + +`joined = ` [[stdlib_strings(module):join(interface)]] ` (strings, separator)` + +#### Status + +Experimental + +#### Class + +Pure function + +#### Argument + +- `strings`: Array of strings (either `type(string_type)` or `character(len=*)`). + This argument is `intent(in)`. It is an array of strings that will be concatenated together. +- `separator`: `character(len=*)` scalar (optional). + 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. + +#### Result value + +The result is of the same type as the elements of `strings` (`type(string_type)` or `character(len=:), allocatable`). + +#### Example + +```fortran +{!example/strings/example_join.f90!} +``` ### `to_string` @@ -498,3 +535,38 @@ The result is an `allocatable` length `character` scalar with up to `128` cached ```fortran {!example/strings/example_to_string.f90!} ``` + + +### `to_c_char` + +#### Description + +Convert a Fortran `character` string or a `type(string_type)` variable to a C character array. +This function converts a Fortran string into a C-style array of characters, ensuring proper null-termination for use in C functions or libraries. + +#### Syntax + +`cstr = ` [[stdlib_strings(module):to_c_char(function)]] ` (value)` + +#### Status + +Experimental + +#### Class + +Pure function. + +#### Argument + +- `value`: Shall be a `character(len=*)` string or a `type(string_type)` variable. It is an `intent(in)` argument. + This Fortran variable will be converted to a C character array. + +#### Result value + +The result is a `character(kind=c_char)` array with a dimension of `len(value) + 1` to accommodate the null terminator. + +#### Example + +```fortran +{!example/strings/example_to_c_char.f90!} +``` diff --git a/example/strings/CMakeLists.txt b/example/strings/CMakeLists.txt index cbaf4f0f3..cdf4d778c 100644 --- a/example/strings/CMakeLists.txt +++ b/example/strings/CMakeLists.txt @@ -2,6 +2,7 @@ ADD_EXAMPLE(chomp) ADD_EXAMPLE(count) ADD_EXAMPLE(ends_with) ADD_EXAMPLE(find) +ADD_EXAMPLE(join) ADD_EXAMPLE(padl) ADD_EXAMPLE(padr) ADD_EXAMPLE(replace_all) @@ -9,6 +10,7 @@ ADD_EXAMPLE(slice) ADD_EXAMPLE(starts_with) ADD_EXAMPLE(strip) ADD_EXAMPLE(to_string) +ADD_EXAMPLE(to_c_char) ADD_EXAMPLE(zfill) ADD_EXAMPLE(string_to_number) -ADD_EXAMPLE(stream_of_strings_to_numbers) \ No newline at end of file +ADD_EXAMPLE(stream_of_strings_to_numbers) diff --git a/example/strings/example_join.f90 b/example/strings/example_join.f90 new file mode 100644 index 000000000..8d60b720d --- /dev/null +++ b/example/strings/example_join.f90 @@ -0,0 +1,20 @@ +program example_join + use stdlib_strings, only: join + implicit none + + character(len=:), allocatable :: line + character(*), parameter :: words(3) = [character(7) :: "Hello", "World", "Fortran"] + + ! Default separator (space) + line = join(words) + print *, "'" // line // "'" !! 'Hello World Fortran' + + ! Custom separator + line = join(words, "_") + print *, "'" // line // "'" !! 'Hello_World_Fortran' + + ! Custom 2-character separator + line = join(words, ", ") + print *, "'" // line // "'" !! 'Hello, World, Fortran' + +end program example_join diff --git a/example/strings/example_to_c_char.f90 b/example/strings/example_to_c_char.f90 new file mode 100644 index 000000000..e15190446 --- /dev/null +++ b/example/strings/example_to_c_char.f90 @@ -0,0 +1,20 @@ +program example_to_c_char + use stdlib_strings, only: to_c_char + use stdlib_string_type, only: string_type + use stdlib_kinds, only: c_char + implicit none + + character(kind=c_char), allocatable :: cstr(:),cstr2(:) + character(*), parameter :: hello = "Hello, World!" + + ! Convert character array + cstr = to_c_char(hello) + + ! Convert string type + cstr2 = to_c_char(string_type(hello)) + + if (size(cstr)/=size(cstr2) .or. .not.all(cstr==cstr2)) then + error stop 'String conversion error' + end if + +end program example_to_c_char diff --git a/src/stdlib_kinds.fypp b/src/stdlib_kinds.fypp index f6b7726c1..ed578e846 100644 --- a/src/stdlib_kinds.fypp +++ b/src/stdlib_kinds.fypp @@ -4,10 +4,10 @@ !> The specification of this module is available [here](../page/specs/stdlib_kinds.html). module stdlib_kinds use iso_fortran_env, only: int8, int16, int32, int64 - use iso_c_binding, only: c_bool + use iso_c_binding, only: c_bool, c_char implicit none private - public :: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool + public :: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool, c_char !> Single precision real numbers integer, parameter :: sp = selected_real_kind(6) diff --git a/src/stdlib_strings.fypp b/src/stdlib_strings.fypp index a70bb38d2..d3e268e54 100644 --- a/src/stdlib_strings.fypp +++ b/src/stdlib_strings.fypp @@ -5,16 +5,18 @@ !> The specification of this module is available [here](../page/specs/stdlib_strings.html). module stdlib_strings use stdlib_ascii, only: whitespace - use stdlib_string_type, only: string_type, char, verify, repeat, len + use stdlib_string_type, only: string_type, char, verify, repeat, len, len_trim, move use stdlib_optval, only: optval - use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool + use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool, c_char + use iso_c_binding, only: c_null_char implicit none private public :: to_string + public :: to_c_char public :: strip, chomp public :: starts_with, ends_with - public :: slice, find, replace_all, padl, padr, count, zfill + public :: slice, find, replace_all, padl, padr, count, zfill, join !> Version: experimental !> @@ -43,6 +45,15 @@ module stdlib_strings #:endfor end interface to_string + !> Version: experimental + !> + !> Format or transfer other types as a string. + !> ([Specification](../page/specs/stdlib_strings.html#to_c_char)) + interface to_c_char + module procedure to_c_char_from_char + module procedure to_c_char_from_string + end interface to_c_char + !> Remove leading and trailing whitespace characters. !> !> Version: experimental @@ -164,6 +175,17 @@ module stdlib_strings module procedure :: zfill_char end interface zfill + !> Version: experimental + !> + !> Joins an array of strings into a single string. + !> The chunks are separated with a space, or an optional user-defined separator. + !> [Specifications](../page/specs/stdlib_strings.html#join) + interface join + module procedure :: join_string + module procedure :: join_char + end interface join + + contains @@ -943,5 +965,97 @@ contains end function zfill_char + !> Convert a Fortran character string to a C character array + !> + !> Version: experimental + pure function to_c_char_from_char(value) result(cstr) + character(len=*), intent(in) :: value + character(kind=c_char) :: cstr(len(value)+1) + integer :: i,lv + lv = len(value) + do concurrent (i=1:lv) + cstr(i) = value(i:i) + end do + cstr(lv+1) = c_null_char + end function to_c_char_from_char + + !> Convert a Fortran string type to a C character array + !> + !> Version: experimental + pure function to_c_char_from_string(value) result(cstr) + type(string_type), intent(in) :: value + character(kind=c_char) :: cstr(len(value)+1) + integer :: i,lv + lv = len(value) + do concurrent (i=1:lv) + cstr(i) = char(value,pos=i) + end do + cstr(lv+1) = c_null_char + end function to_c_char_from_string + + !> Joins a list of strings with a separator (default: space). + !> Returns a new string + pure type(string_type) function join_string(strings, separator) + type(string_type), intent(in) :: strings(:) + character(len=*), intent(in), optional :: separator + integer :: ltot, i, lt, pos + character(len=:), allocatable :: sep,joined + ! Determine separator: use user-provided separator or default space + if (present(separator)) then + sep = separator + else + sep = ' ' + end if + ! Calculate the total length required, including separators + ltot = sum(len_trim(strings)) + (size(strings) - 1) * len(sep) + allocate(character(len=ltot) :: joined) + + ! Concatenate strings with separator + pos = 0 + do i = 1, size(strings) + lt = len_trim(strings(i)) + joined(pos+1:pos+lt) = char(strings(i),1,lt) + pos = pos + lt + if (i < size(strings)) then + joined(pos+1:pos+len(sep)) = sep + pos = pos + len(sep) + end if + end do + + call move(from=joined,to=join_string) + + end function join_string + + !> Joins a list of strings with a separator (default: space). + !> Returns a new string + pure function join_char(strings, separator) result(joined) + character(*), intent(in) :: strings(:) + character(len=*), intent(in), optional :: separator + character(len=:), allocatable :: joined + integer :: ltot, i, lt, pos + character(len=:), allocatable :: sep + ! Determine separator: use user-provided separator or default space + if (present(separator)) then + sep = separator + else + sep = ' ' + end if + ! Calculate the total length required, including separators + ltot = sum(len_trim(strings)) + (size(strings) - 1) * len(sep) + allocate(character(len=ltot) :: joined) + + joined = repeat(' ',ltot) + ! Concatenate strings with separator + pos = 0 + do i = 1, size(strings) + lt = len_trim(strings(i)) + joined(pos+1:pos+lt) = strings(i)(1:lt) + pos = pos + lt + if (i < size(strings)) then + joined(pos+1:pos+len(sep)) = sep + pos = pos + len(sep) + end if + end do + end function join_char end module stdlib_strings diff --git a/test/string/test_string_match.f90 b/test/string/test_string_match.f90 index a41821b10..be835ae7e 100644 --- a/test/string/test_string_match.f90 +++ b/test/string/test_string_match.f90 @@ -2,7 +2,7 @@ module test_string_match use testdrive, only : new_unittest, unittest_type, error_type, check use stdlib_ascii, only : reverse - use stdlib_strings, only : starts_with, ends_with + use stdlib_strings, only : starts_with, ends_with, join use stdlib_string_type, only : string_type implicit none @@ -16,7 +16,8 @@ subroutine collect_string_match(testsuite) testsuite = [ & new_unittest("starts_with", test_starts_with), & - new_unittest("ends_with", test_ends_with) & + new_unittest("ends_with", test_ends_with), & + new_unittest("join", test_join) & ] end subroutine collect_string_match @@ -77,6 +78,32 @@ subroutine check_ends_with(error, string, substring) call check(error, ends_with(string_type(string), string_type(substring)) .eqv. match, message) end subroutine check_ends_with + subroutine test_join(error) + type(error_type), allocatable, intent(out) :: error + character(len=5) :: test_strings(3) + + test_strings = [character(5) :: "one", "two", "three"] + call check_join(error, test_strings, " ", "one two three") + if (allocated(error)) return + call check_join(error, test_strings, ",", "one,two,three") + if (allocated(error)) return + call check_join(error, test_strings, "-", "one-two-three") + end subroutine test_join + + subroutine check_join(error, strings, separator, expected) + type(error_type), allocatable, intent(out) :: error + character(len=*), intent(in) :: strings(:) + character(len=*), intent(in) :: separator + character(len=*), intent(in) :: expected + character(len=:), allocatable :: joined + character(len=:), allocatable :: message + + joined = join(strings, separator) + message = "'join' error: Expected '" // expected // "' but got '" // joined // "'" + call check(error, joined == expected, message) + + end subroutine check_join + subroutine test_ends_with(error) type(error_type), allocatable, intent(out) :: error call check_ends_with(error, "pattern", "pat") diff --git a/test/string/test_string_to_string.f90 b/test/string/test_string_to_string.f90 index 5f7be6886..6465c7003 100644 --- a/test/string/test_string_to_string.f90 +++ b/test/string/test_string_to_string.f90 @@ -1,7 +1,7 @@ ! SPDX-Identifier: MIT module test_string_to_string - use stdlib_strings, only: to_string, starts_with + use stdlib_strings, only: to_string, to_c_char, starts_with use testdrive, only : new_unittest, unittest_type, error_type, check use stdlib_optval, only: optval implicit none @@ -22,7 +22,8 @@ subroutine collect_string_to_string(testsuite) new_unittest("to_string-limit-i1", test_string_i1), & new_unittest("to_string-limit-i2", test_string_i2), & new_unittest("to_string-limit-i4", test_string_i4), & - new_unittest("to_string-limit-i8", test_string_i8) & + new_unittest("to_string-limit-i8", test_string_i8), & + new_unittest("to_c_char", test_to_c_char) & ] end subroutine collect_string_to_string @@ -149,6 +150,49 @@ subroutine test_to_string_logical(error) end subroutine test_to_string_logical + subroutine test_to_c_char(error) + use stdlib_kinds, only : c_char + use stdlib_string_type, only: string_type, len, char + use iso_c_binding, only: c_size_t + + !> Error handling + type(error_type), allocatable, intent(out) :: error + + !> Interface to C standard library + interface + integer(c_size_t) function c_strlen(cstr) bind(C, name="strlen") result(len) + import :: c_char, c_size_t + character(kind=c_char), intent(in) :: cstr(*) + end function c_strlen + end interface + + type(string_type) :: shello + character(kind=c_char), allocatable :: cstr(:) + character(*), parameter :: hello = "Hello, World!" + integer :: i + + ! Convert character array + cstr = to_c_char(hello) + call check(error, len(hello)==c_strlen(cstr), 'to_c_char_from_char: invalid C length') + if (allocated(error)) return + + do i=1,len(hello) + call check(error, hello(i:i)==cstr(i), 'to_c_char_from_char: character mismatch') + if (allocated(error)) return + end do + + ! Convert string type + shello = string_type(hello) + cstr = to_c_char(shello) + call check(error, len(shello)==c_strlen(cstr), 'to_c_char_from_string: invalid C length') + if (allocated(error)) return + + do i=1,len(shello) + call check(error, char(shello,pos=i)==cstr(i), 'to_c_char_from_string: character mismatch') + if (allocated(error)) return + end do + + end subroutine test_to_c_char subroutine test_string_i1(error) use stdlib_kinds, only : i1 => int8