Skip to content

Commit 2dd83d9

Browse files
committed
Rename function from to_char to to_string
1 parent 0f714df commit 2dd83d9

File tree

3 files changed

+29
-29
lines changed

3 files changed

+29
-29
lines changed

src/stdlib_ascii.fypp

+9-9
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
@@ -328,7 +328,7 @@ contains
328328

329329
#:for kind in INT_KINDS
330330
!> Represent an integer of kind ${kind}$ as character sequence
331-
pure function to_char_integer_${kind}$(val) result(string)
331+
pure function to_string_integer_${kind}$(val) result(string)
332332
integer, parameter :: ik = ${kind}$
333333
integer(ik), intent(in) :: val
334334
character(len=:), allocatable :: string
@@ -359,18 +359,18 @@ contains
359359
end if
360360

361361
string = buffer(pos:)
362-
end function to_char_integer_${kind}$
362+
end function to_string_integer_${kind}$
363363
#:endfor
364364

365365
#:for kind in INT_KINDS
366366
!> Represent an logical of kind ${kind}$ as character sequence
367-
pure function to_char_logical_${kind}$(val) result(string)
367+
pure function to_string_logical_${kind}$(val) result(string)
368368
integer, parameter :: ik = ${kind}$
369369
logical(ik), intent(in) :: val
370370
character(len=1) :: string
371371

372372
string = merge("T", "F", val)
373-
end function to_char_logical_${kind}$
373+
end function to_string_logical_${kind}$
374374
#:endfor
375375

376376
end module stdlib_ascii

src/stdlib_string_type.fypp

+3-3
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414
!> The specification of this module is available [here](../page/specs/stdlib_string_type.html).
1515
module stdlib_string_type
1616
use stdlib_ascii, only: to_lower_ => to_lower, to_upper_ => to_upper, &
17-
& to_title_ => to_title, reverse_ => reverse, to_char
17+
& to_title_ => to_title, reverse_ => reverse, to_string
1818
use stdlib_kinds, only : int8, int16, int32, int64
1919
implicit none
2020
private
@@ -361,7 +361,7 @@ contains
361361
elemental function new_string_from_integer_${kind}$(val) result(new)
362362
integer(${kind}$), intent(in) :: val
363363
type(string_type) :: new
364-
new%raw = to_char(val)
364+
new%raw = to_string(val)
365365
end function new_string_from_integer_${kind}$
366366
#:endfor
367367

@@ -370,7 +370,7 @@ contains
370370
elemental function new_string_from_logical_${kind}$(val) result(new)
371371
logical(${kind}$), intent(in) :: val
372372
type(string_type) :: new
373-
new%raw = to_char(val)
373+
new%raw = to_string(val)
374374
end function new_string_from_logical_${kind}$
375375
#:endfor
376376

src/tests/ascii/test_ascii.f90

+17-17
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)