1+ #:include "common.fypp"
2+
13!> The `stdlib_ascii` module provides procedures for handling and manipulating
24!> intrinsic character variables and constants.
35!>
46!> The specification of this module is available [here](../page/specs/stdlib_ascii.html).
57module stdlib_ascii
8+ use stdlib_kinds, only : int8, int16, int32, int64
69
710 implicit none
811 private
@@ -17,6 +20,17 @@ module stdlib_ascii
1720
1821 ! Character conversion functions
1922 public :: to_lower, to_upper, to_title, reverse
23+ public :: to_string
24+
25+ !> Version: experimental
26+ !>
27+ !> Create a character string representing the value of the provided variable.
28+ interface to_string
29+ #:for kind in INT_KINDS
30+ module procedure :: to_string_integer_${kind}$
31+ module procedure :: to_string_logical_${kind}$
32+ #:endfor
33+ end interface to_string
2034
2135 ! All control characters in the ASCII table (see www.asciitable.com).
2236 character(len=1), public, parameter :: NUL = achar(int(z'00')) !! Null
@@ -312,4 +326,51 @@ pure function reverse(string) result(reverse_string)
312326
313327 end function reverse
314328
329+ #:for kind in INT_KINDS
330+ !> Represent an integer of kind ${kind}$ as character sequence
331+ pure function to_string_integer_${kind}$(val) result(string)
332+ integer, parameter :: ik = ${kind}$
333+ integer(ik), intent(in) :: val
334+ character(len=:), allocatable :: string
335+ integer, parameter :: buffer_len = range(val)+2
336+ character(len=buffer_len) :: buffer
337+ integer :: pos
338+ integer(ik) :: n
339+ character(len=1), parameter :: numbers(0:9) = &
340+ ["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"]
341+
342+ if (val == 0_ik) then
343+ string = numbers(0)
344+ return
345+ end if
346+
347+ n = abs(val)
348+ buffer = ""
349+
350+ pos = buffer_len + 1
351+ do while (n > 0_ik)
352+ pos = pos - 1
353+ buffer(pos:pos) = numbers(mod(n, 10_ik))
354+ n = n/10_ik
355+ end do
356+ if (val < 0_ik) then
357+ pos = pos - 1
358+ buffer(pos:pos) = '-'
359+ end if
360+
361+ string = buffer(pos:)
362+ end function to_string_integer_${kind}$
363+ #:endfor
364+
365+ #:for kind in INT_KINDS
366+ !> Represent an logical of kind ${kind}$ as character sequence
367+ pure function to_string_logical_${kind}$(val) result(string)
368+ integer, parameter :: ik = ${kind}$
369+ logical(ik), intent(in) :: val
370+ character(len=1) :: string
371+
372+ string = merge("T", "F", val)
373+ end function to_string_logical_${kind}$
374+ #:endfor
375+
315376end module stdlib_ascii
0 commit comments