I prefer to initialize 64-bit integer variables with 64-bit real values. It is convenient to use scientific notation. Just want to ask if there is any risk of doing that.
integer(8) :: x 
x = 3d9
I prefer to initialize 64-bit integer variables with 64-bit real values. It is convenient to use scientific notation. Just want to ask if there is any risk of doing that.
integer(8) :: x 
x = 3d9
For values similar to 3d9, only the range can be a problem. But if you try to use multi-digit values, you have to keep in mind that there are integer values which cannot be represented in FP because the number of mantissa bits is smaller than 64.
Maybe you could write it like this to be on the safe side:
x = 3 * 10_8**9
Obviously it is longer, but at least the type is correct.
If you don’t like the _8 you can (and it would be more robust anyway) define a kind for this, e.g.
use iso_fortran_env, only: l => int64
integer(l) :: x
x = 3*10_l**12
or
integer, parameter :: l = selected_int_kind(18)
Curious, what do you need such large integers for? I don’t think I’ve ever hard-coded a value that big in a real application.
In a perfect world, there would be widespread support for the Fortran 2018 intrinsic out_of_range, so you could be paranoid and do
use, intrinsic :: iso_fortran_env, only: real64, int64
integer(int64) :: x
if  (.not. out_of_range(3e9_real64, mold=x)) then 
  x = int(3e9_real64, int64)
else
  error stop "Not representable as int64"
end if
end
But as far as I know, this is not widely implemented.
What @fortran4r wrote works for 3d9, but I wonder how to recover the correct integer when the floating point value is near huge(i). I was going to suggest using the nint function, but the output of the program
program convert
use iso_fortran_env, only: int64
implicit none
integer, parameter :: dp = kind(1.0d0)
real(kind=dp) :: x,x0
integer(kind=int64) :: i,j,k
do j=0,512
   k = huge(i) - j
   x = real(k,kind=dp)
   if (j == 0) x0 = x
   i = x
   if (modulo(j,100_int64) == 0 .or. i > 0) print*,j,k,x0==x,x,i,nint(x,kind=int64)
end do
end program convert
is
                    0  9223372036854775807 T   9.2233720368547758E+018 -9223372036854775808 -9223372036854775808
                  100  9223372036854775707 T   9.2233720368547758E+018 -9223372036854775808 -9223372036854775808
                  200  9223372036854775607 T   9.2233720368547758E+018 -9223372036854775808 -9223372036854775808
                  300  9223372036854775507 T   9.2233720368547758E+018 -9223372036854775808 -9223372036854775808
                  400  9223372036854775407 T   9.2233720368547758E+018 -9223372036854775808 -9223372036854775808
                  500  9223372036854775307 T   9.2233720368547758E+018 -9223372036854775808 -9223372036854775808
                  512  9223372036854775295 F   9.2233720368547748E+018  9223372036854774784  9223372036854774784
so the signs of the integer variables are reversed for x equal to huge(i) but not huge(i)-512.
That shows clearly the problem which I mentioned above. Not all integer values are representable in FP value of the same size. That is why first six integers are all converted to the very same DP value.
The second part is, however, worrying. IMHO the conversion of the DP value back into integer should not change the sign. According to the Standard, the assignment i=x is equivalent to i=INT(x,kind=kind(i)) (10.2.1.3.8, Table 10.9). And the description if INT() states (16.9.100.5, case(ii)):
If A is of type real, there are two cases: if |A| < 1, INT (A) has the value 0; if |A| ≥ 1, INT (A) is the integer whose magnitude is the largest integer that does not exceed the magnitude of A and whose sign is the same as the sign of A.
So, for positive value of x, the result should be largest integer less or equal x and definitely with positive sign.
Interestingly, the NINT() column, when using gfortran v.11.2, shows, correctly, all positive values (6x 9223372036854775807 and 9223372036854774784 in the last row). With ifort (2021.4.0) I am getting the same output as @Beliavsky.
I work with long arrays whose size is longer than 2^31 - 1
As suggested upthread, you are likely to satisfy your conveniences here with mnemonics:
   ..
   integer, parameter :: I8 = selected_int_kind( r=10 )
   ..
   integer(I8), parameter :: TEN = 10_i8
   ..
   integer(I8) :: x
   ..
   x = 3*TEN**9
Given what you write re: risk, you may want to consider staying away from hard-wired values such as 8 for integer kind.