Skip to content

Commit 23e535b

Browse files
committed
to_c_string -> to_c_char: rename
1 parent e902e5c commit 23e535b

File tree

5 files changed

+29
-29
lines changed

5 files changed

+29
-29
lines changed

doc/specs/stdlib_strings.md

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -537,7 +537,7 @@ The result is an `allocatable` length `character` scalar with up to `128` cached
537537
```
538538

539539
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
540-
### `to_c_string`
540+
### `to_c_char`
541541

542542
#### Description
543543

@@ -546,7 +546,7 @@ This function converts a Fortran string into a C-style array of characters, ensu
546546

547547
#### Syntax
548548

549-
`cstr = ` [[stdlib_strings(module):to_c_string(function)]] ` (value)`
549+
`cstr = ` [[stdlib_strings(module):to_c_char(function)]] ` (value)`
550550

551551
#### Status
552552

@@ -568,5 +568,5 @@ The result is a `character(kind=c_char)` array with a dimension of `len(value) +
568568
#### Example
569569

570570
```fortran
571-
{!example/strings/example_to_c_string.f90!}
571+
{!example/strings/example_to_c_char.f90!}
572572
```

example/strings/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ ADD_EXAMPLE(slice)
1010
ADD_EXAMPLE(starts_with)
1111
ADD_EXAMPLE(strip)
1212
ADD_EXAMPLE(to_string)
13-
ADD_EXAMPLE(to_c_string)
13+
ADD_EXAMPLE(to_c_char)
1414
ADD_EXAMPLE(zfill)
1515
ADD_EXAMPLE(string_to_number)
1616
ADD_EXAMPLE(stream_of_strings_to_numbers)
Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
program example_to_c_string
2-
use stdlib_strings, only: to_c_string
1+
program example_to_c_char
2+
use stdlib_strings, only: to_c_char
33
use stdlib_string_type, only: string_type
44
use stdlib_kinds, only: c_char
55
implicit none
@@ -8,15 +8,15 @@ program example_to_c_string
88
character(*), parameter :: hello = "Hello, World!"
99

1010
! Convert character array
11-
cstr = to_c_string(hello)
11+
cstr = to_c_char(hello)
1212

1313
! Convert string type
14-
cstr2 = to_c_string(string_type(hello))
14+
cstr2 = to_c_char(string_type(hello))
1515

1616
if (size(cstr)==size(cstr2) .and. all(cstr==cstr2)) then
1717
stop 0
1818
else
1919
error stop 'String conversion error'
2020
end if
2121

22-
end program example_to_c_string
22+
end program example_to_c_char

src/stdlib_strings.fypp

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ module stdlib_strings
1313
private
1414

1515
public :: to_string
16-
public :: to_c_string
16+
public :: to_c_char
1717
public :: strip, chomp
1818
public :: starts_with, ends_with
1919
public :: slice, find, replace_all, padl, padr, count, zfill, join
@@ -48,11 +48,11 @@ module stdlib_strings
4848
!> Version: experimental
4949
!>
5050
!> Format or transfer other types as a string.
51-
!> ([Specification](../page/specs/stdlib_strings.html#to_c_string))
52-
interface to_c_string
53-
module procedure to_c_string_from_char
54-
module procedure to_c_string_from_string
55-
end interface to_c_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
5656

5757
!> Remove leading and trailing whitespace characters.
5858
!>
@@ -968,7 +968,7 @@ contains
968968
!> Convert a Fortran character string to a C character array
969969
!>
970970
!> Version: experimental
971-
pure function to_c_string_from_char(value) result(cstr)
971+
pure function to_c_char_from_char(value) result(cstr)
972972
character(len=*), intent(in) :: value
973973
character(kind=c_char) :: cstr(len(value)+1)
974974
integer :: i,lv
@@ -977,12 +977,12 @@ contains
977977
cstr(i) = value(i:i)
978978
end do
979979
cstr(lv+1) = c_null_char
980-
end function to_c_string_from_char
980+
end function to_c_char_from_char
981981

982982
!> Convert a Fortran string type to a C character array
983983
!>
984984
!> Version: experimental
985-
pure function to_c_string_from_string(value) result(cstr)
985+
pure function to_c_char_from_string(value) result(cstr)
986986
type(string_type), intent(in) :: value
987987
character(kind=c_char) :: cstr(len(value)+1)
988988
integer :: i,lv
@@ -991,7 +991,7 @@ contains
991991
cstr(i) = char(value,pos=i)
992992
end do
993993
cstr(lv+1) = c_null_char
994-
end function to_c_string_from_string
994+
end function to_c_char_from_string
995995

996996
!> Joins a list of strings with a separator (default: space).
997997
!> Returns a new string

test/string/test_string_to_string.f90

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
! SPDX-Identifier: MIT
22
module test_string_to_string
33

4-
use stdlib_strings, only: to_string, to_c_string, starts_with
4+
use stdlib_strings, only: to_string, to_c_char, starts_with
55
use testdrive, only : new_unittest, unittest_type, error_type, check
66
use stdlib_optval, only: optval
77
implicit none
@@ -23,7 +23,7 @@ subroutine collect_string_to_string(testsuite)
2323
new_unittest("to_string-limit-i2", test_string_i2), &
2424
new_unittest("to_string-limit-i4", test_string_i4), &
2525
new_unittest("to_string-limit-i8", test_string_i8), &
26-
new_unittest("to_c_string", test_to_c_string) &
26+
new_unittest("to_c_char", test_to_c_char) &
2727
]
2828
end subroutine collect_string_to_string
2929

@@ -150,7 +150,7 @@ subroutine test_to_string_logical(error)
150150

151151
end subroutine test_to_string_logical
152152

153-
subroutine test_to_c_string(error)
153+
subroutine test_to_c_char(error)
154154
use stdlib_kinds, only : c_char
155155
use stdlib_string_type, only: string_type, len, char
156156
use iso_c_binding, only: c_size_t
@@ -172,27 +172,27 @@ end function c_strlen
172172
integer :: i
173173

174174
! 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')
175+
cstr = to_c_char(hello)
176+
call check(error, len(hello)==c_strlen(cstr), 'to_c_char_from_char: invalid C length')
177177
if (allocated(error)) return
178178

179179
do i=1,len(hello)
180-
call check(error, hello(i:i)==cstr(i), 'to_c_string_from_char: character mismatch')
180+
call check(error, hello(i:i)==cstr(i), 'to_c_char_from_char: character mismatch')
181181
if (allocated(error)) return
182182
end do
183183

184184
! Convert string type
185185
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')
186+
cstr = to_c_char(shello)
187+
call check(error, len(shello)==c_strlen(cstr), 'to_c_char_from_string: invalid C length')
188188
if (allocated(error)) return
189189

190190
do i=1,len(shello)
191-
call check(error, char(shello,pos=i)==cstr(i), 'to_c_string_from_string: character mismatch')
191+
call check(error, char(shello,pos=i)==cstr(i), 'to_c_char_from_string: character mismatch')
192192
if (allocated(error)) return
193193
end do
194194

195-
end subroutine test_to_c_string
195+
end subroutine test_to_c_char
196196

197197
subroutine test_string_i1(error)
198198
use stdlib_kinds, only : i1 => int8

0 commit comments

Comments
 (0)