Skip to content

Commit adacbcf

Browse files
committed
to_c_string: move to strings, document
1 parent 79ddfc4 commit adacbcf

File tree

3 files changed

+46
-9
lines changed

3 files changed

+46
-9
lines changed

doc/specs/stdlib_strings.md

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -498,3 +498,33 @@ The result is an `allocatable` length `character` scalar with up to `128` cached
498498
```fortran
499499
{!example/strings/example_to_string.f90!}
500500
```
501+
502+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
503+
### `to_c_string`
504+
505+
#### Description
506+
507+
Convert a Fortran character string to a C character array.
508+
This function converts a Fortran string into a C-style string, ensuring proper null-termination for use in C functions or libraries.
509+
510+
#### Syntax
511+
512+
`cstr = ` [[stdlib_strings(module):to_c_string(function)]] ` (value)`
513+
514+
#### Status
515+
516+
Experimental
517+
518+
#### Class
519+
520+
Pure function.
521+
522+
#### Argument
523+
524+
- `value`: Shall be a `character(len=*)` string.
525+
This is an `intent(in)` argument.
526+
The Fortran string that will be converted to a C character array.
527+
528+
#### Result value
529+
530+
The result is a `character(kind=c_char)` array with a dimension of `len(value) + 1` to accommodate the null terminator.

src/stdlib_strings.fypp

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,12 @@ module stdlib_strings
88
use stdlib_string_type, only: string_type, char, verify, repeat, len
99
use stdlib_optval, only: optval
1010
use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool
11+
use iso_c_binding, only: c_char, c_null_char
1112
implicit none
1213
private
1314

1415
public :: to_string
16+
public :: to_c_string
1517
public :: strip, chomp
1618
public :: starts_with, ends_with
1719
public :: slice, find, replace_all, padl, padr, count, zfill
@@ -943,5 +945,17 @@ contains
943945

944946
end function zfill_char
945947

948+
!> Convert a Fortran character string to a C character array
949+
!>
950+
!> Version: experimental
951+
pure function to_c_string(value) result(cstr)
952+
character(len=*), intent(in) :: value
953+
character(kind=c_char) :: cstr(len(value)+1)
954+
integer :: i
955+
do concurrent (i=1:len(value))
956+
cstr(i) = value(i:i)
957+
end do
958+
cstr(len(value)+1) = c_null_char
959+
end function to_c_string
946960

947961
end module stdlib_strings

src/stdlib_system_subprocess.F90

Lines changed: 2 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@ module fortran_subprocess
22
use iso_c_binding
33
use iso_fortran_env, only: int64, real64
44
use stdlib_system
5+
use stdlib_io, only: getfile
6+
use stdlib_strings, only: to_c_string
57
implicit none
68
public
79

@@ -199,15 +201,6 @@ subroutine launch_asynchronous(process, args, stdin)
199201

200202
end subroutine launch_asynchronous
201203

202-
pure function c_string(str) result(cstr)
203-
character(*), intent(in) :: str
204-
character(c_char), allocatable :: cstr(:)
205-
integer :: i
206-
allocate(cstr(len(str)+1))
207-
forall(i=1:len(str)) cstr(i) = str(i:i)
208-
cstr(len(str)+1) = c_null_char
209-
end function c_string
210-
211204
subroutine launch_synchronous(process, args, stdin)
212205
class(process_type), intent(inout) :: process
213206
!> The command and arguments

0 commit comments

Comments
 (0)