Efficiency and suitability of using floats, decimals and integers

I have a lot of equations where I have resolved all values used within a double precision variable’s calculations as double precisions.

For example…

radnab = (3d0 * 10**kappa * luminosity * pressure) / (6.4d1 * gfs * PI * SIGMA * mass* temperature**4)

In the case of these values, should I keep 3d0 as that, or would it be better/acceptable to put 3.0; or can I represent it as an integer (3)?

Similarly, is it okay to replace 6.4d1 with 64.0 or even 64?

Do I lose or gain anything if I convert 3.333d-1 into 0.3333?

For integer literals, I’d recommend leaving them as integers. They’re (the vast majority of the time) exactly representable as floating point values, and the automatic conversion rules of the language will handle things correctly and efficiently. For fractional literals I’d recommend not using d##, but instead _dp (or other appropriately defined kind constant) that matches the kind of the rest of the variables used in the expression. For the value 0.3333, it looks like you probably want (1.0 / 3.0), so I’d actually recommend declaring it as a constant, i.e. real(dp), parameter :: one_third = 1.0_dp / 3.0_dp and using that in the expression.

A quick note about terminology, Fortran has numeric types real, integer, and complex, so when you say “floats, decimals, and integers” I don’t know what you mean by “decimals”.

1 Like

You sometimes need to be careful with expressions like this. On a 32-bit integer machine, you will get an overflow for kappa>9, while 10.0_wp**kappa will work alright until you get up to the floating point overflow range, which is around 307. Overflow means either that your job crashes or that you silently get the wrong number, so both things are bad. Of course, if you know that kappa is always <9, then you are alright.

3 Likes

This sounds reasonnable when you know what you’re doing, but there are some traps for the beginners here. @RonShepard raised a case where some integer overflow could arise, but there is also things like 64 / 3 * x (x being a real) that won’t give the expected result if one thinks that the compiler automatically casts all the integer constants to reals (it doesn’t).

By the way, I’m not sure if this case: 64 * x / 3 is 100% safe or not ? The standard says that the expression shall be evaluated from left to right, i.e. (64 * x) / 3(64.0 * x) / 3(64.0 *x) / 3.0, but also that the compiler is free to reorder the evaluations if they are mathematically equivalent. 64.0 / 3.0 * x is mathematically equivalent to 64.0 * x / 3.0, but 64 / 3 * x is not mathematically equivalent to 64 * x / 3, so the latter case the compiler is not allowed to reorder the evaluations: do we agree?

Thanks for the replies.

I have had the KIND option offered to me before but I could not see the benefit. On searching the web I simply seem to create myself more confusion.

Let me use the example from @everythingfunctional

If I were to create this parameter, I would have used double precision, parameter :: one_third = 1d0 / 3d0

To me, the KIND alternative is less ‘tidy’? Terrible grammar but you know what I am referencing (I hope).

I’m not sure if losing precision on my 1/3 is important at this point (I also have others, including 2/3). Originally these were defined as xdy**(1d0/3d0) and, since I knew the value it helped me tidy up the equations. I considered there to be a minor time gain from using the calculated result rather than keep the division - and it helped me identify a couple of the equations. However, I will change it one of the alternatives shortly - I now gain nothing from my alteration and, clearly, lose precision.

Again, @RonShepard gives me the 10.0_wp**kappa structure, where I originally had 1d1**kappa and now went to the (more likely to generate an issue) 10**kappa. This takes me back to my issue of using a decimal part (10.0**kappa, or the alternatives already given, rather than the literal integer of 10**kappa) - thus, for safety’s sake (listening to @PierU), using 64.0 * x rather than 64 * x - where the latter is easier to read but I run the risk of errors(?)

I’m also interested in your comments on the fact:

64.0 / 3.0 * x is mathematically equivalent to 64.0 * x / 3.0, but 64 / 3 * x is not mathematically equivalent to 64 * x / 3

Why is the former equivalent but not the latter? Probably being very thick (I have my moments), but cannot see the reasoning. Is this down to the casting of the values (as real or integer?).

Oh, and @everythingfunctional, sorry, yes, I am working across multiple programming languages with a wide range of data type names. I use decimal for realand float for double precision. This has less to do with programming, actually, and more to do with databases - which is something else I do. Please be aware, I am old enough to only have 1k of RAM in my head (running at 12MHz on an 8-bit processor) - I mix and match as I type (I usually type as I think). I will endeavour to do better. :slight_smile:

This is because the / operator does not represent the same thing depending on the operands:

With 64 * x / 3 what the compiler does is (real(64) * x) / real(3), and ‘/’ is the floating point division.

With 64 / 3 * x what the compiler does is real(64 / 3) * real(3), and ‘/’ is the integer division.

The floating point division and the integer division are not mathematically equivalent, hence my interpretation (but I’m not 100% sure, and in practice I prefer writing 64.0 * x / 3.0 to avoid any issue)

Ah, I see. So, in Fortran there is no distinct difference between the representation of division and integer division - this is decided by the variable types being used?

I have not come across this before. Normally, / is plain old division, always resulting in a fractional value.

Indeed, the integer division is applied if the two operands are of integer type. Otherwise the floating point division is applied (after integer to real casting if needed)

3 / 2 = 1
3.0 / 2 = 3.0 / real(2) = 1.5
3 / 2.0 = real(3) / 2.0 = 1.5
3.0 / 2.0 = 1.5

Indeed, I missed the couple of caveats. My apologies. Perhaps I should also always recommend make sure you are unit testing your complicated expressions.

1 Like

Everything about the fortran KIND system is a benefit. There are no practical downsides at all. This is one of the best features of the fortran language.

This is maybe a little to brief. The first expression is really more like

(real(64,kind(x)) * x) / real(3,kind(x))

That is, the compiler converts the integer values directly to the kind of the real number in the operation. The way it was written originally might be interpreted as two steps, first conversion to the default real kind, then conversion of that to kind(x), and then the multiplication or division operation. This distinction might be important if precision would be lost with real(i) but not with real(i,kind(x)).

If a programmer is inclined, he can write out the conversions explicitly as above, and the compiler will produce the exact same machine instructions. The only difference is that in one case it is explicit while in the other the default mixed-type and mixed-kind conversion rules are imposed implicitly.

The other feature to note is that if the programmer uses parentheses, then it is clear which order of operations and conversions is done. The compiler is required to respect the parentheses groupings (unlike C, which for a couple of decades was not required to do so). The compiler knows what to do, but a human programmer might not catch all of the subtleties, especially if he programs in several languages with sometimes different semantics and operator precedence. As with the explicit use of type and kind conversion operators, the redundant parentheses do not cost anything, the exact same machine instructions are generated in all cases. As a matter of style, sometimes you will see mixed type expressions written as

(((64) * x) / (3))

This is still using the fortran language default conversion semantics, but the extra parentheses in (64) and (3) are used to draw attention to the type conversion without being too verbose about it. This also occurs when variables are used rather than constants, particularly variables whose types might not be obvious from their names, e.g. (((a) * x) / (b)) for integer a and b.

Indeed… I was thinking “x is default real” but only wrote “x is real”… So it was worth correcting.

Yes, I had forgotten that!

It is, I think, unusual. Hence why it doesn’t stick in the memory (and how easy it would be to overlook it).

Thank you. :slight_smile:

Yes, I can see that, and can see how your code is the neater for it.

I was curious with Ron’s statement…

The thing is that all examples I could find relating to KIND all added levels of complexity to lines of code that made each line harder to read, not easier - so, it was difficult to see any true advantage.

I remain curious about the mixed use of 1.d0 and 1d0. Throughout the examples I find both given; though in this post the former is common. Again, is there reasoning behind this?

The ones to avoid are

x = 1 / 3
x = 1_knd / 3
x = 1 / 3_knd
x = 1_knd / 3_knd

This assumes that the real kind parameter knd also happens to be a valid integer kind. In these cases, these are all integer divisions that evaluate to 0, and are then converted to real 0.0_knd.

Consider this simple program:

program kinds
   integer, parameter :: k4 = 4, k8=8, k10=10, k16=16
   write(*,*) 1.0_k4 + 2.0_k8 + 3.0_k10 + 4.0_k16
end program kinds

This compiles with gfortran on intel hardware. Of course, it is not really portable because of the hardwired kind values, but I hope you see the point. How could you do that kind of mixed-precision arithmetic in such a simple way in any other language? Or even in fortran without using its KIND facility. And when new kinds are added in the future, as they almost certainly will be, they can fit right into the open-ended system.

So, the benefit of the KIND is the portability across different compilers and, therefore, systems? I know that my double precisions ARE double precisions using KIND, rather than assuming the compiler is applying the definition effectively?

If so, how big an issue is this?

My ‘concern’ is that this appears to add a little more confusion to the code, albeit tiny in most cases (if I am correct on its usage).

One of the functions I now have is this one…

	double precision function radnab(kappa, luminosity, totalPressure, gfs, mass, temperature)
	
	    use stellar_values, only: PI, SIGMA
	    implicit none
	    double precision, intent(in) :: kappa, luminosity, totalPressure, gfs, mass, temperature
	    save
	
	    radnab = (3d0 * 10.0**kappa * luminosity * totalPressure) / (6.4d1 * gfs * PI * SIGMA * mass * temperature**4)
	    return
	end function radnab

I am assuming that I would gain the same accuracy, but better portability, if I did this?

	double precision function radnab(kappa, luminosity, totalPressure, gfs, mass, temperature)
	
	    use stellar_values, only: PI, SIGMA
	    implicit none
	    double precision, intent(in)   :: kappa, luminosity, totalPressure, gfs, mass, temperature
        integer, parameter             :: DP = kind(0d0)
        double precision(kind = DP)    :: d
	    save
	
	    radnab = (3.0_d * 10.0**kappa * luminosity * totalPressure) / (64.0 * gfs * PI * SIGMA * mass * temperature**4)
	    return
	end function radnab

Am I understanding this correctly, @RonShepard ?

In the context of this thread, this all may be further confusing.

During a similar inquiry at another forum, @macneacail in this comment refers to the great help provided by @mecej4 in setting up a module that can readily be used in codes. Someone may want to guide OP here similarly, perhaps along the following lines given the focus on “double precision” as opposed to any flexibility with different precisions:

But the point will be to help OP arrive at a stage where the literal constants only appear once in code during the definition only of mnemonic named constants such as ONE, … TWOTHIRDS, c (for speed of light), etc. All expressions in Fortran code shall then consistently make use of such named constants only, as opposed to literal values.

Without such discipline, it will be back to square one and endless confusion with mixed-mode arithmetic in Fortran codes.

module constants_m
   .
   integer, parameter :: DP = kind(1d0)
   .
   real(DP), parameter :: ONE = 1.0_dp
   real(DP), parameter :: TWO = 2.0_dp
   real(DP), parameter :: THREE = 3.0_dp
   .
   .
   real(DP), parameter :: ONETHIRD = ONE/THREE
   .
   .
end module
  • Then in other code, perhaps for some astrophysics calculation
module astroxx_m
   .
   use constants_m
   .
contains
   .
   subroutine some_calc( .. )
      .
      real(DP) = x, y
      .
      x = ..
      y = x**ONETHIRD  !<-- no use of literal constant, only a named one
      .

P.S.> Edit as pointed out by @RonShepard below

I already have a modules file, where I include the necessary modules as and when necessary. So, it would be easy for me to either include the definitions in my primary module (stellar_values) or create a new one.
The stellar_values module contains all my ‘constants’ (C, G, SIGMA, etc).
I will reread your latest post and see where that takes me.
Yes, the code only uses logical, integer, character or double precision. I assume that I am correct in that KIND is used due to portability across compilers/systems; so I would simply need to define a KIND for double precision? Integer values are all low and unlikely to exceed any compiler limit.
I haven’t used a module across multiple subroutines/functions before (I’m assuming that’s what your last example is indicating), but none of that is problematic.

That is one of the benefits, but it is not the one I demonstrated. The one I demonstrated is how easy it is to set up mixed-precision expressions. The challenge is to show how to set up an equivalent expression without using the fortran kinds facility. You will find it is either impossible or very tedious.

There are many other advantages, such as the ability to write an entire project using the kinds facility where if you want to change the kind, you can do so in a single line of code, and then have that propagate through any number of levels of USE statements throughout the whole project. In contrast, if you rely on E and D exponents throughout the code, then you must make thousands of local text edits in order to accomplish the same thing.

And there are many other advantages. As I said before, everything about the fortran kinds facility is an advantage, there are no real downsides in any way at all. This is one of the best features of fortran.

I thought it was obvious, but let me spell it out. The context of the discussion was when to use explicit decimal points when specifying real constants. I showed some examples where the decimal point is essential. Even though those constants look like they are real values, because they use the real knd parameter, they aren’t. This is a not uncommon mistake with new programmers, and I thought entirely within the context of the discussion.