Skip to content

Commit

Permalink
Avoid overflow in to_string for -huge(1)-1 (#667)
Browse files Browse the repository at this point in the history
  • Loading branch information
awvwgk authored Jul 22, 2022
1 parent f98f3d3 commit 9c4abca
Show file tree
Hide file tree
Showing 2 changed files with 60 additions and 15 deletions.
29 changes: 15 additions & 14 deletions src/stdlib_strings_to_string.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ contains
${t1}$, intent(in) :: value
character(len=*), intent(in), optional :: format
character(len=:), allocatable :: string

character(len=buffer_len) :: buffer
integer :: stat

Expand Down Expand Up @@ -43,30 +43,31 @@ contains
#:for k1, t1 in INT_KINDS_TYPES
!> Represent an integer of kind ${k1}$ as character sequence.
pure module function to_string_1_${t1[0]}$_${k1}$(value) result(string)
${t1}$, intent(in) :: value
integer, parameter :: ik = ${k1}$
integer(ik), intent(in) :: value
character(len=:), allocatable :: string
integer, parameter :: buffer_len = range(value)+2
character(len=buffer_len) :: buffer
integer :: pos
${t1}$ :: n
character(len=1), parameter :: numbers(0:9) = &
["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"]
integer(ik) :: n
character(len=1), parameter :: numbers(-9:0) = &
["9", "8", "7", "6", "5", "4", "3", "2", "1", "0"]

if (value == 0_${k1}$) then
if (value == 0_ik) then
string = numbers(0)
return
end if

n = abs(value)
n = sign(value, -1_ik)
buffer = ""

pos = buffer_len + 1
do while (n > 0_${k1}$)
do while (n < 0_ik)
pos = pos - 1
buffer(pos:pos) = numbers(mod(n, 10_${k1}$))
n = n/10_${k1}$
buffer(pos:pos) = numbers(mod(n, 10_ik))
n = n/10_ik
end do
if (value < 0_${k1}$) then

if (value < 0_ik) then
pos = pos - 1
buffer(pos:pos) = '-'
end if
Expand All @@ -78,7 +79,7 @@ contains
${t1}$, intent(in) :: value
character(len=*), intent(in) :: format
character(len=:), allocatable :: string

character(len=buffer_len) :: buffer
integer :: stat

Expand Down Expand Up @@ -106,7 +107,7 @@ contains
${t1}$, intent(in) :: value
character(len=*), intent(in) :: format
character(len=:), allocatable :: string

character(len=buffer_len) :: buffer
integer :: stat

Expand Down
46 changes: 45 additions & 1 deletion src/tests/string/test_string_to_string.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,11 @@ subroutine collect_string_to_string(testsuite)
new_unittest("to_string-complex", test_to_string_complex), &
new_unittest("to_string-integer", test_to_string_integer), &
new_unittest("to_string-logical", test_to_string_logical), &
new_unittest("to_string-real", test_to_string_real) &
new_unittest("to_string-real", test_to_string_real), &
new_unittest("to_string-limit-i1", test_string_i1), &
new_unittest("to_string-limit-i2", test_string_i2), &
new_unittest("to_string-limit-i4", test_string_i4), &
new_unittest("to_string-limit-i8", test_string_i8) &
]
end subroutine collect_string_to_string

Expand Down Expand Up @@ -146,6 +150,46 @@ subroutine test_to_string_logical(error)
end subroutine test_to_string_logical


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

!> Error handling
type(error_type), allocatable, intent(out) :: error

call check(error, to_string(-huge(1_i1) - 1_i1), "-128")
end subroutine test_string_i1


subroutine test_string_i2(error)
use stdlib_kinds, only : i2 => int16

!> Error handling
type(error_type), allocatable, intent(out) :: error

call check(error, to_string(-huge(1_i2) - 1_i2), "-32768")
end subroutine test_string_i2


subroutine test_string_i4(error)
use stdlib_kinds, only : i4 => int32

!> Error handling
type(error_type), allocatable, intent(out) :: error

call check(error, to_string(-huge(1_i4) - 1_i4), "-2147483648")
end subroutine test_string_i4


subroutine test_string_i8(error)
use stdlib_kinds, only : i8 => int64

!> Error handling
type(error_type), allocatable, intent(out) :: error

call check(error, to_string(-huge(1_i8) - 1_i8), "-9223372036854775808")
end subroutine test_string_i8


end module test_string_to_string


Expand Down

0 comments on commit 9c4abca

Please sign in to comment.