Flags for kind casting warning for parameters?

Hello I have some code where an integer kind parameter is cast to a real as part of my calculation:

program lennard_jones_potential
    !! Calculates the Lennard-Jones Potential for 2 Xenon atoms

    use, intrinsic :: iso_fortran_env, only: i_64 => int64, r_64 => real64

    implicit none

    real(kind=r_64),    parameter :: epsilon = 0.997_r_64  ! kJ/mol
      !! well depth kJ/mol
    real(kind=r_64),    parameter :: sigma = 3.40_r_64     ! Angstroms
      !! van der Waals radius Angstroms
    integer(kind=i_64), parameter :: lj_potential_const = 4_i_64
      !! unit-less Lennard-Jones Potential constant

    real(kind=r_64) :: separation_distance
      !! separation distance r in Angstroms
    real(kind=r_64) :: lj_potential
      !! Lennard-Jones Potential kJ/mol

    separation_distance = 4.0_r_64  ! Angstroms

    ! Calculate the Lennard-Jones Potential using:
    ! V(r) = 4*epsilon*[(sigma/r)**12 - (sigma/r)**6]
    lj_potential = lj_potential_const * epsilon * &
                   ((sigma/separation_distance)**12 &
                   - (sigma/separation_distance)**6)

    print *, 'V(4.0 Angstrom) = ', lj_potential, ' kJ/mol'

end program lennard_jones_potential

If I compile this with:

gfortran -o ljp lennard_jones_potential.f90 -Wconversion -Wconversion-extra

I get no warnings about the casting. Why is that?
If I remove parameter and recompile I DO get a warning about casting from int to real!
GNU Fortran (GCC) 11.5.0 20240719

1 Like

I am puzzled that you apparently need 64 bits of precision to specify the number 4.

My guess is that when named constants are used, the compiler knows that multiplication by 4 can be implemented by changing the binary exponent of a real and cannot produce an inexact result (although it could overflow). When it is marked as a variable, the compiler does not consider the initial value 4 and promotion of a 64-bit integer to a 64-bit real can in general be inexact (there are only 53 mantissa bits in the real), hence the warning.

2 Likes

I’m just guessing, but I think the lj_potential_const*epsilon product is evaluated at compile time in one case and at run time in the other. The compile time evaluation probably bypasses the conversion warnings.

This is a little outside of my field of expertise, but when I look at codes that need to compute LJ potentials efficiently, they usually factor that expression so that all the exponentials are replaced with simple multiplications. You might expect a compiler to do some of that automatically, but probably not all of it.

You could argue that analysis, that the optimizer phase does later, should reveal that there is one basic block in this code and LJ_POTENTIAL_COST is only ever 4 which should/could then suppress the warning. But this is just not how most compilers choose to do things, the early phases’ warnings make it out to the user before the optimizer gets a look in.

Thanks both, the lj_potential_const variable is 64 bit to avoid mixed precision.
The compiler does appear to be doing some magic under the hood - if I change the parameter to 4.2 then the warning appears!

The lj_potential_const is an integer, so it is not possible to set it to a value of 4.2. Since it is an integer, the compiler must convert it to a real according to the implicit conversion rules when evaluating the expression. The expression

lj_potential_const * epsilon

must be evaluated as real(lj_potential_const,kind(epsilon))*epsilon no matter what kind of integer, int8, int16, int32, or int64. The integer value of 4 can of course be represented exactly with any of those integer kinds. As stated previously, it appears that this conversion and multiplication are done at compile time when both entities are parameter constants, and at run time when one or both are variables. This might not be done by the optimizer (backend), it might be just part of the semantic parsing (front end). One would need to examine the intermediate code or the machine code that is produced by the compiler to know for sure.

I mentioned that the energy expression can be computed with only multiplications and no exponential evaluations. This is an outline of how that might work.

real(r_64), parameter :: x = 4.0_r_64 * 0.997_r_64
real(r_64) :: t, t3, t6
t = sigma/separation_distance
t3 = t * t * t
t6 = t3 * t3
lj_potential = x * (t6+t3) * (t6-t3)

There are some other equivalent expressions that can be used, but this gives the general idea. LJ potentials have a long history, so it might be useful to examine some of the mature legacy codes to see what kind of evaluation tricks have been used in the past for the efficiency/accuracy tradeoffs.

Ah yes I missed the warning changed when attempting to set an integer with a real.
I still feel it should warn when using an integer parameter instead of just doing clever stuff in the background.

This is just a test program to use as training material so although the multiplication only code is interesting I think the exponential eval version will do. Thanks for all your help!

The warniing would be appropriate when the integer value cannot be converted exactly to the floating point value. Or more generally, when the expression is not defined within the language, then various compilers might make different choices in how it is evaluated and the code would not be portable. In this case, the expression itself is defined within the language, so that second situation does not apply. Because the small integer can be converted exactly to floating point (regardless of the KINDs in this case), there is no danger of precision loss for the first situation either. As noted in the original post, a compiler might post a warning for this or it might not, even with compiler options enabled in the attempt to identify potentially erroneous or imprecise situations. All of the other possible evaluation errors for this expression, namely underflows or overflows, are the same for the floating point expression as they are for the mixed mode expression.

One other point that I perhaps should have mentioned previously, any time you need to evaluate an expression like x*x-y*y, it is always better to evaluate it as (x+y)*(x-y). First, it replaces two multiplies and one addition with two additions and one multiply, which is almost always more efficient. But also the first expression is less accurate than the second expression when x is approximately equal to y. It is an interesting exercise to see why that occurs. If you can’t figure it out by yourself, then a google search on “evaluation of x*x-y*y floating point” will lead you to various discussions of this feature of floating point arithmetic. For the LJ potential, this will occur when separation_distance is close to sigma, which is in the repulsive part of the curve. One might hope that a good optimizing compiler would make this substitution automatically, but this is probably beyond what will occur even with aggressive compiler options.

2 Likes