Skip to content

Commit 1322b08

Browse files
committed
Add functions to convert integer/logical values to character values
- use fypp in stdlib_ascii to generate functions for all kind values
1 parent 0886501 commit 1322b08

File tree

5 files changed

+150
-3
lines changed

5 files changed

+150
-3
lines changed

doc/specs/stdlib_ascii.md

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -169,3 +169,42 @@ program demo_reverse
169169
print'(a)', reverse("Hello, World!") ! returns "!dlroW ,olleH"
170170
end program demo_reverse
171171
```
172+
173+
174+
### `char_value`
175+
176+
#### Status
177+
178+
Experimental
179+
180+
#### Description
181+
182+
Create a character string representing the value of the provided variable.
183+
184+
#### Syntax
185+
186+
`res = [[stdlib_ascii(module):char_value(interface)]] (string)`
187+
188+
#### Class
189+
190+
Pure function.
191+
192+
#### Argument
193+
194+
`val`: shall be an intrinsic integer or logical type. It is an `intent(in)` argument.
195+
196+
#### Result value
197+
198+
The result is an intrinsic character type.
199+
200+
#### Example
201+
202+
```fortran
203+
program demo_char_value
204+
use stdlib_ascii, only : char_value
205+
implicit none
206+
print'(a)', char_value(-3) ! returns "-3"
207+
print'(a)', char_value(.true.) ! returns "T"
208+
print'(a)', char_value(42) ! returns "42"
209+
end program demo_char_value
210+
```

src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22

33
# Create a list of the files to be preprocessed
44
set(fppFiles
5+
stdlib_ascii.fypp
56
stdlib_bitsets.fypp
67
stdlib_bitsets_64.fypp
78
stdlib_bitsets_large.fypp
@@ -37,7 +38,6 @@ endif()
3738
fypp_f90("${fyppFlags}" "${fppFiles}" outFiles)
3839

3940
set(SRC
40-
stdlib_ascii.f90
4141
stdlib_error.f90
4242
stdlib_kinds.f90
4343
stdlib_logger.f90

src/Makefile.manual

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
SRCFYPP =\
2+
stdlib_ascii.fypp \
23
stdlib_bitsets_64.fypp \
34
stdlib_bitsets_large.fypp \
45
stdlib_bitsets.fypp \
@@ -21,7 +22,6 @@ SRCFYPP =\
2122
stdlib_stats_distribution_PRNG.fypp
2223

2324
SRC = f18estop.f90 \
24-
stdlib_ascii.f90 \
2525
stdlib_error.f90 \
2626
stdlib_kinds.f90 \
2727
stdlib_logger.f90 \

src/stdlib_ascii.f90 renamed to src/stdlib_ascii.fypp

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,11 @@
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).
57
module 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 :: char_value
24+
25+
!> Version: experimental
26+
!>
27+
!> Create a character string representing the value of the provided variable.
28+
interface char_value
29+
#:for kind in INT_KINDS
30+
module procedure :: integer_${kind}$_to_char
31+
module procedure :: logical_${kind}$_to_char
32+
#:endfor
33+
end interface char_value
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 integer_${kind}$_to_char(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 integer_${kind}$_to_char
363+
#:endfor
364+
365+
#:for kind in INT_KINDS
366+
!> Represent an logical of kind ${kind}$ as character sequence
367+
pure function logical_${kind}$_to_char(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 logical_${kind}$_to_char
374+
#:endfor
375+
315376
end module stdlib_ascii

src/tests/ascii/test_ascii.f90

Lines changed: 48 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,9 @@ program test_ascii
66
whitespace, letters, is_alphanum, is_alpha, is_lower, is_upper, &
77
is_digit, is_octal_digit, is_hex_digit, is_white, is_blank, &
88
is_control, is_punctuation, is_graphical, is_printable, is_ascii, &
9-
to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL
9+
to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL, &
10+
char_value
11+
use stdlib_kinds, only : int8, int16, int32, int64
1012

1113
implicit none
1214

@@ -73,6 +75,8 @@ program test_ascii
7375
call test_to_title_string
7476
call test_reverse_string
7577

78+
call test_char_value
79+
7680
contains
7781

7882
subroutine test_is_alphanum_short
@@ -613,4 +617,47 @@ subroutine test_reverse_string
613617
call check(trim(adjustl(dlc)) == "desrever")
614618
end subroutine test_reverse_string
615619

620+
subroutine test_char_value
621+
character(len=128) :: flc
622+
623+
write(flc, '(g0)') 1026192
624+
call check(char_value(1026192) == trim(flc))
625+
626+
write(flc, '(g0)') -124784
627+
call check(char_value(-124784) == trim(flc))
628+
629+
write(flc, '(g0)') 1_int8
630+
call check(char_value(1_int8) == trim(flc))
631+
632+
write(flc, '(g0)') -3_int8
633+
call check(char_value(-3_int8) == trim(flc))
634+
635+
write(flc, '(g0)') 80_int16
636+
call check(char_value(80_int16) == trim(flc))
637+
638+
write(flc, '(g0)') 8924890_int32
639+
call check(char_value(8924890_int32) == trim(flc))
640+
641+
write(flc, '(g0)') -2378401_int32
642+
call check(char_value(-2378401_int32) == trim(flc))
643+
644+
write(flc, '(g0)') -921092378401_int64
645+
call check(char_value(-921092378401_int64) == trim(flc))
646+
647+
write(flc, '(g0)') 1272835771_int64
648+
call check(char_value(1272835771_int64) == trim(flc))
649+
650+
write(flc, '(g0)') .true.
651+
call check(char_value(.true.) == trim(flc))
652+
653+
write(flc, '(g0)') .false.
654+
call check(char_value(.false.) == trim(flc))
655+
656+
write(flc, '(g0)') .true._int8
657+
call check(char_value(.true._int8) == trim(flc))
658+
659+
write(flc, '(g0)') .false._int64
660+
call check(char_value(.false._int64) == trim(flc))
661+
end subroutine test_char_value
662+
616663
end program test_ascii

0 commit comments

Comments
 (0)