Can floating point literals be adapted by the compiler to double precision variable?

@JohnCampbell thanks for the post with the historical explanation and welcome to the Forum!

The “64” in x86_64 and 64-bit ARM refers to the number of bits in the memory addresses, not the default size of reals.

Correct. A = 1, A = 1.0, and A = 1.00000000 should all produce the same internal floating point bits since 1.0 has an exact representation in the IEEE binary floating point representations. Besides, trailing zeros do not affect the value of a floating point constant. The value 0.1 does not have an exact representation, so is quite different from 1.0.

@billlong,

Yes, 64 bit does refer to 64-bit addressing. However most Fortran compilers that migrated from 32-bit OS to 64-bit OS retained 32-bit default size integers and reals, eg ifort and gFortran. This was preferred to enable easier conversion and testing, with selective use of 64-bit integers in the new Fortran code for memory addressing and larger arrays. Changing to default 64-bit integers and reals would have created a lot more work when converting Fortran codes, so less take-up of the new compilers.
However, with 64-bit OS, there is a much greater need for 64-bit integers, but there was not as easy a change to large integer constants as there has been for 64-bit reals, which are in more typical use with most 32-bit compilers.
Where previously, many allocatable arrays were configured with default integer constants, these now have to be made 64-bit throughout the code. They are often routine arguments. Real functions, like DDOTP (N, DX, DY) or DAXPY (N,DA,DX,DY) now must support 64-bit N, which can be transferred throughout the 32-bit code. It is not unusual to find the approach of DDOTP8 or DAXPY8 as alternative larger addressing functions, as a quick fix, rather than a rigorous migration to 64-bit support.
Have you ever defined an integer constant “integer(int64) :: four_gbytes = 4 * 1024**3”, forgetting the integer constants used are only 32-bits, even when defining a 64-bit integer ? These can be a common annoyance when scaling up from a previous 32-bit code examples.
SIZE (array) can also provide unexpected result, such as “write (,) ‘array size =’,size(array)”

Another “common gotcha” ?

We slowly learn not to cut corners!

2 Likes

Yes, I’ve been bitten by this many times. Also, as you mentioned, in allocating and handling large arrays, I can’t remember the exact details. We should add this to our gotcha’s list that we need to start.

@billlong I am just trying to understand the reasoning behind Cray’s choice. You said that Cray used to use 64bit default reals on the classic vector machines. My understanding of Cray I is that it was a 64-bit system. So how is that conceptually different from x86_64 which is also a 64-bit system? So if the reasoning was to use 64-bit default real on Cray I, why not to use 64-bit default real on x86_64?

@JohnCampbell provided one explanation: that the evolution was via 32-bit systems first, and then changing it back to 64-bit would break codes, so they just stuck with 32-bit default real. That makes perfect sense.

That’s the question in 2021… It’s now a very long time since I used a 32 bits microprocessor for the last time… 15 years? more?

1 Like

Doing that would run into problems, given that the Fortran standard has a requirement that (i) at least two real types should be provided, and (ii) double precision should have higher precision than single precision. In the absence of hardware 128-bit (now quadruple, proposed double) precision, double (new) precision calculations (which would have higher precision than 64-bit IEEE) would be quite slow.

There are many simulations that run fine at present with single-precision reals (32 bits, of which 23+1 are mantissa). These codes would need to be recompiled with a compiler flag that selects 32-bit reals for REAL if the default has become 64-bit. Or, if 64-bit default reals are to be used in the future, all constants in the programs will need to be modified to be 64-bit real constants.

Sudden changes in default behavior also run afoul of the Principle of Minimum Surprise.

2 Likes

Concerning those two points, it does not seem that changing the default reals changes anything: single precision would still be available by choosing the right kind…

1 Like

The Cray 1 was a very different machine from modern microprocessors.

  1. The smallest addressable block of memory was 64 bits. Yes that means that individual characters took 64 bits.
  2. Integers were just the mantissa of floating point numbers with an exponent of 0. I believe that gave the equivalent of something like 50 bit integers.
  3. “DOUBLE PRECISION” was software emulated and ran more than an order of magnitude slower than “REAL” precision.
2 Likes

How about integer off-the-range constants? It seems that at least some compilers treat them somewhat inconsistently. The standard says that a literal integer constant without a kind parameter should be treated as default integer type. Consider following code:

  integer, parameter :: ik=selected_int_kind(12), dp=kind(1d0)
  integer(kind=ik)   :: i
  integer :: j
  real(kind=dp) :: x
  real :: y
  i = 20000000000_ik
  x = 1.2345678901234567_dp
  j = i
  y = x
  print *, i, j, x, y
!    20000000000 -1474836480   1.2345678901234567   1.23456788

So far, so good. Now let’s remove the kind parameters

[...]
i = 20000000000
x = 1.2345678901234567
[...]

Gfortran (9.3.0) gives an error: Integer too big for its kind unless -fno-range-check option is used. Intel oneAPI ifort (2021.3.0) compiles w/o any warnings. Both (gfortran with the option) output, surprisingly in the integer part:

!      20000000000 -1474836480   1.2345678806304932   1.23456788

I would expect both integer values “overflowed”. Apparently the off-the-range constant of 20 billion is treated as 64-bit value, not the default 32. Not as in the real case, where the constant w/o ‘_dp’ is converted to single real value before assignment to a double variable. And this happens not only with extra decimal digits, as if changed to x = 1.2345678901234567e100, it becomes ‘Infinity’.

1 Like

ifort -stand:f18 offrange.f90

does say

offrange.f90(6): warning #8221: An integer constant outside the default integer range is not standard Fortran 2018 - using INTEGER(8).   [20000000000]
  i = 20000000000 ! _ik
------^
1 Like

That was obvious even without this warning. I am just curious why reals are treated somewhat differently (not saying it is necessarily not standard-conforming). The same invocation of ifort -stand:f18 with the real assignment

  x = 1.2345678901234567e100

gives just ‘remark’ (not even warning):

litconst.f90(9): remark #7960: The floating overflow condition was detected while evaluating this operation; the result is an Infinity. [1.2345678901234567E100]

So it seems as if real off-the-range constants are converted to default real type (be it truncation or infinity) while the integer ones are treated as non-default type instead. Shouldn’t the -stand:f18 option cause error on something that is “not standard Fortran 2018”?

1 Like

This is such an annoying historical feature of modern Fortran.

Lets consider the following example code. Real constants like 0.1 or 0.7 would have been very common in the 70’s and 80’s, such as when lots of code was developed for finite element analysis.

   Real*8 x, y, e
   character string*10

   x = 0.7    ! 0.1
   y = x*10
   e = 7 - y  ! 1 - y
   write (*,*) x,y,e

   string = ' 0.7 '
   read (string,*) x
   y = x*10
   e = 7 - y
   write (*,*) x,y,e
   end

If I compiled this on Lahey F77 or Sun or Apollo Fortran, the “0.7” would have been promoted to 0.7D0 (or better), with the constant stored in a 64bit or 80bit register. This was common practice for most 32-bit Fortran compilers at that time, as the compiler recognised the implied precision of “0.7” .
For the second part of the test where 0.7 is read from a string or file, both F77 and F90+ will get the same result.
Move forward to F90 and these updated compilers had to introduce precision failings to be conforming.
For those on the standard committee to introduce/force such a precision failure in so many historical Fortran codes, is just riidculous. I do wonder what Tom Lahey said about this.

There is all this discussion about what is error prone coding, much of which is basically style based bias. (COMMON is now bad but thousands of lines of code for OOP definitions is not error prone?)
F90 introduced generic intrinsics, but now there is all this class coding for supporting different variable kind/type. Many lines of code that must correctly interact. Is this progress ?

How many actual Fortran users would say that real*8 should be stamped out, or a Module might not be a global saved data structure ?
There should be more consideration of Fortran users when changing the rules in the Fortran standard…

Implicit none and the d0 suffix are sufficient to scare away most people. No matter how many new features are to be added, these two things will always be joked about.

2 Likes

The standard allows the floating point model to be different at runtime and compilation time. The Absoft compiler illustrates the issues that this may cause which a user needs to be aware of.

In a certain program, the constant 1.0d70 had been used to signify ‘infinity’ or ‘undefined’ or ‘end of data’. The following program shows how this may not work as intended.

      PROGRAM FPBUG
      DOUBLE PRECISION SIGMA,BND
      character*6 sSigma
      DATA SIGMA /1.0D70/,sSigma/'1.0D70'/

      READ (sSigma,*) BND
      write(*,10)BND,SIGMA,BND.GT.SIGMA
   10 format(1x,1p,D24.17,' > ',D24.17,' ?  ',L5)
      END

Most compilers will produce code that prints ‘.F.’ for the last I/O item. The output from the Absoft-compiled program:

  1.00000000000000000D+70 >  1.00000000000000000D+70 ?      T

If I understand this 2023-May-28 file https://j3-fortran.org/doc/year/23/23-154.txt
we can hope this proposal (“Program-specified default KINDs for constants and intrinsic”) will be recommended to WG5 for inclusion in Fortran 202Y.

1 Like

I really doubt about that… 5.35 being interpreted as the default real type was true even in F77.

As explained by @wclodius , the vector Cray machines were quite atypical ones. And having a 64 bits default REAL was actually sometimes a source of frustration because it meant twice the memory occupation in the cases where 32 bits REALs were enough. For memory critical applications it was frustrating.

This discussion actually ignores that there exists scientific applications dealing with huge data volumes and where “more memory, please” is a constant wish. I know tons of codes where the data are primarily in 32 bits reals, and that just temporarily use 64 bits reals where needed. Not to mention the 16 bits or even 8 bits reals that become popular in machine learning. Also, storing the data in 32 bits can actually result in faster codes in the case of memory bound algorithms.

That said, being able to select the default kind on programming unit basis looks like a good proposal.

I think fortran programmers of that era were more accustomed to “atypical” behavior. There were at that time many computers where the default real was 64, 60, 36, 32, and even 24 bits. Of course, hardware address spaces then were typically in the 16 to 24 bit range, so that had little to do with the default real size.

Regarding Cray in particular, I used several of the 64-bit real machines in the 1980s, and then I switched over to using mostly RISC machines in the 1990s. Then Cray was bought and sold several times. I think SGI owned cray for a while, and they built and sold RISC-based machines at that time. I think that might have been when the Cray compilers switched to default 32-bit real and integer data sizes. Then later, maybe in the early 2000s, Cray ended up with AMD chips, which were also 32-bit real and integer defaults, and that was the first time I ran into problems matching fortran code with library routines because there were so many possibilities. I remember thinking at that time that things would probably have been simpler to just stick with default 64-bit real and integers throughout that time.

On a separate issue, Cray characters (in their cft77 compiler) were 8-bits, not 64-bits. There were 8 characters per 64-bit word. I think this made character processing slow, but memory was so limited at that time, that was the compromise that was chosen. People used Crays for their floating point performance, not for their character processing abilities.

That claim sounds odd to me too. I was concerned with writing portable code then, and I was aware that some compilers would change the types of some literals (e.g. in data statements), but I avoided using that feature because not all compilers did that (and standard f77 did not require it in any situation). I always tried to either specify the type (with an E or a D exponent) or I defined parameter constants of the correct type (e.g. as actual arguments to subprograms). In hindsight, all of that now seems very primitive and limiting. The current modern fortran type/kind approach is much better in every respect.

I have to disagree that type(kind) is preferable to more simply having distinct types. The same problems exist in either system, except that we must also have a solution to the idea of a “default kind.” That would not even be a question if there were, more simply, many distinct types.

In a similar vein on the topic of backwards compatibility, since that seems to be a major concern whenever large changes are discussed, why not add to the standard a way to programatically declare what standard (I believe Rust uses a similar concept with “versions”) a scoping unit of code is written in? Having such capability would do away with a great number of complaints such as “having default implicit none would break legacy code.”

No Fortran standard declared in a scoping unit would default to the last standard prior to the addition of this feature, such as Fortran 202X. That way, the language could radically evolve moving forward, with support for all kinds of commonly requested features and no fear of breaking backwards compatibility.