Skip to content

Commit 1b25dde

Browse files
committed
Rename function from to_char to to_string
1 parent 5fa920d commit 1b25dde

File tree

3 files changed

+29
-29
lines changed

3 files changed

+29
-29
lines changed

src/stdlib_ascii.fypp

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -20,17 +20,17 @@ module stdlib_ascii
2020

2121
! Character conversion functions
2222
public :: to_lower, to_upper, to_title, reverse
23-
public :: to_char
23+
public :: to_string
2424

2525
!> Version: experimental
2626
!>
2727
!> Create a character string representing the value of the provided variable.
28-
interface to_char
28+
interface to_string
2929
#:for kind in INT_KINDS
30-
module procedure :: to_char_integer_${kind}$
31-
module procedure :: to_char_logical_${kind}$
30+
module procedure :: to_string_integer_${kind}$
31+
module procedure :: to_string_logical_${kind}$
3232
#:endfor
33-
end interface to_char
33+
end interface to_string
3434

3535
! All control characters in the ASCII table (see www.asciitable.com).
3636
character(len=1), public, parameter :: NUL = achar(int(z'00')) !! Null
@@ -298,7 +298,7 @@ contains
298298

299299
#:for kind in INT_KINDS
300300
!> Represent an integer of kind ${kind}$ as character sequence
301-
pure function to_char_integer_${kind}$(val) result(string)
301+
pure function to_string_integer_${kind}$(val) result(string)
302302
integer, parameter :: ik = ${kind}$
303303
integer(ik), intent(in) :: val
304304
character(len=:), allocatable :: string
@@ -329,18 +329,18 @@ contains
329329
end if
330330

331331
string = buffer(pos:)
332-
end function to_char_integer_${kind}$
332+
end function to_string_integer_${kind}$
333333
#:endfor
334334

335335
#:for kind in INT_KINDS
336336
!> Represent an logical of kind ${kind}$ as character sequence
337-
pure function to_char_logical_${kind}$(val) result(string)
337+
pure function to_string_logical_${kind}$(val) result(string)
338338
integer, parameter :: ik = ${kind}$
339339
logical(ik), intent(in) :: val
340340
character(len=1) :: string
341341

342342
string = merge("T", "F", val)
343-
end function to_char_logical_${kind}$
343+
end function to_string_logical_${kind}$
344344
#:endfor
345345

346346
end module stdlib_ascii

src/stdlib_string_type.fypp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
!>
1414
!> The specification of this module is available [here](../page/specs/stdlib_string_type.html).
1515
module stdlib_string_type
16-
use stdlib_ascii, only : to_char
16+
use stdlib_ascii, only : to_string
1717
use stdlib_kinds, only : int8, int16, int32, int64
1818
implicit none
1919
private
@@ -327,7 +327,7 @@ contains
327327
elemental function new_string_from_integer_${kind}$(val) result(new)
328328
integer(${kind}$), intent(in) :: val
329329
type(string_type) :: new
330-
new%raw = to_char(val)
330+
new%raw = to_string(val)
331331
end function new_string_from_integer_${kind}$
332332
#:endfor
333333

@@ -336,7 +336,7 @@ contains
336336
elemental function new_string_from_logical_${kind}$(val) result(new)
337337
logical(${kind}$), intent(in) :: val
338338
type(string_type) :: new
339-
new%raw = to_char(val)
339+
new%raw = to_string(val)
340340
end function new_string_from_logical_${kind}$
341341
#:endfor
342342

src/tests/ascii/test_ascii.f90

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ program test_ascii
77
is_digit, is_octal_digit, is_hex_digit, is_white, is_blank, &
88
is_control, is_punctuation, is_graphical, is_printable, is_ascii, &
99
to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL, &
10-
to_char
10+
to_string
1111
use stdlib_kinds, only : int8, int16, int32, int64
1212

1313
implicit none
@@ -75,7 +75,7 @@ program test_ascii
7575
call test_to_title_string
7676
call test_reverse_string
7777

78-
call test_char_value
78+
call test_to_string
7979

8080
contains
8181

@@ -617,47 +617,47 @@ subroutine test_reverse_string
617617
call check(trim(adjustl(dlc)) == "desrever")
618618
end subroutine test_reverse_string
619619

620-
subroutine test_char_value
620+
subroutine test_to_string
621621
character(len=128) :: flc
622622

623623
write(flc, '(g0)') 1026192
624-
call check(to_char(1026192) == trim(flc))
624+
call check(to_string(1026192) == trim(flc))
625625

626626
write(flc, '(g0)') -124784
627-
call check(to_char(-124784) == trim(flc))
627+
call check(to_string(-124784) == trim(flc))
628628

629629
write(flc, '(g0)') 1_int8
630-
call check(to_char(1_int8) == trim(flc))
630+
call check(to_string(1_int8) == trim(flc))
631631

632632
write(flc, '(g0)') -3_int8
633-
call check(to_char(-3_int8) == trim(flc))
633+
call check(to_string(-3_int8) == trim(flc))
634634

635635
write(flc, '(g0)') 80_int16
636-
call check(to_char(80_int16) == trim(flc))
636+
call check(to_string(80_int16) == trim(flc))
637637

638638
write(flc, '(g0)') 8924890_int32
639-
call check(to_char(8924890_int32) == trim(flc))
639+
call check(to_string(8924890_int32) == trim(flc))
640640

641641
write(flc, '(g0)') -2378401_int32
642-
call check(to_char(-2378401_int32) == trim(flc))
642+
call check(to_string(-2378401_int32) == trim(flc))
643643

644644
write(flc, '(g0)') -921092378401_int64
645-
call check(to_char(-921092378401_int64) == trim(flc))
645+
call check(to_string(-921092378401_int64) == trim(flc))
646646

647647
write(flc, '(g0)') 1272835771_int64
648-
call check(to_char(1272835771_int64) == trim(flc))
648+
call check(to_string(1272835771_int64) == trim(flc))
649649

650650
write(flc, '(g0)') .true.
651-
call check(to_char(.true.) == trim(flc))
651+
call check(to_string(.true.) == trim(flc))
652652

653653
write(flc, '(g0)') .false.
654-
call check(to_char(.false.) == trim(flc))
654+
call check(to_string(.false.) == trim(flc))
655655

656656
write(flc, '(g0)') .true._int8
657-
call check(to_char(.true._int8) == trim(flc))
657+
call check(to_string(.true._int8) == trim(flc))
658658

659659
write(flc, '(g0)') .false._int64
660-
call check(to_char(.false._int64) == trim(flc))
661-
end subroutine test_char_value
660+
call check(to_string(.false._int64) == trim(flc))
661+
end subroutine test_to_string
662662

663663
end program test_ascii

0 commit comments

Comments
 (0)