11! SPDX-Identifier: MIT
22module test_string_to_string
33
4- use stdlib_strings, only: to_string, starts_with
4+ use stdlib_strings, only: to_string, to_c_string, starts_with
55 use testdrive, only : new_unittest, unittest_type, error_type, check
66 use stdlib_optval, only: optval
77 implicit none
@@ -22,7 +22,8 @@ subroutine collect_string_to_string(testsuite)
2222 new_unittest(" to_string-limit-i1" , test_string_i1), &
2323 new_unittest(" to_string-limit-i2" , test_string_i2), &
2424 new_unittest(" to_string-limit-i4" , test_string_i4), &
25- new_unittest(" to_string-limit-i8" , test_string_i8) &
25+ new_unittest(" to_string-limit-i8" , test_string_i8), &
26+ new_unittest(" to_c_string" , test_to_c_string) &
2627 ]
2728 end subroutine collect_string_to_string
2829
@@ -149,6 +150,49 @@ subroutine test_to_string_logical(error)
149150
150151 end subroutine test_to_string_logical
151152
153+ subroutine test_to_c_string (error )
154+ use stdlib_kinds, only : c_char
155+ use stdlib_string_type, only: string_type, len, char
156+ use iso_c_binding, only: c_size_t
157+
158+ ! > Error handling
159+ type (error_type), allocatable , intent (out ) :: error
160+
161+ ! > Interface to C standard library
162+ interface
163+ integer (c_size_t) function c_strlen(cstr) bind(C, name= " strlen" ) result(len)
164+ import :: c_char, c_size_t
165+ character (kind= c_char), intent (in ) :: cstr(* )
166+ end function c_strlen
167+ end interface
168+
169+ type (string_type) :: shello
170+ character (kind= c_char), allocatable :: cstr(:)
171+ character (* ), parameter :: hello = " Hello, World!"
172+ integer :: i
173+
174+ ! Convert character array
175+ cstr = to_c_string(hello)
176+ call check(error, len (hello)==c_strlen(cstr), ' to_c_string_from_char: invalid C length' )
177+ if (allocated (error)) return
178+
179+ do i= 1 ,len (hello)
180+ call check(error, hello(i:i)==cstr(i), ' to_c_string_from_char: character mismatch' )
181+ if (allocated (error)) return
182+ end do
183+
184+ ! Convert string type
185+ shello = string_type(hello)
186+ cstr = to_c_string(shello)
187+ call check(error, len (shello)==c_strlen(cstr), ' to_c_string_from_string: invalid C length' )
188+ if (allocated (error)) return
189+
190+ do i= 1 ,len (shello)
191+ call check(error, char (shello,pos= i)==cstr(i), ' to_c_string_from_string: character mismatch' )
192+ if (allocated (error)) return
193+ end do
194+
195+ end subroutine test_to_c_string
152196
153197 subroutine test_string_i1 (error )
154198 use stdlib_kinds, only : i1 = > int8
0 commit comments