Best way to declare a double precision in Fortran?

You can place code snippets between two back-ticks (`), i.e. integer*8. For blocks use three backticks (```). This will render then as a monospace/typewriter font.

This is correct, that is not a standard conforming way and it never has been. The modern fortran way is

real(wp) :: step_size = 0.1_wp

which is standard conforming for any real kind wp.

If fortran had adopted a different convention for specifying constants 70 years ago, then things would be different now. But this has been the convention for a long time now, and unless someone can propose a backward compatible way to change this convention, it is unlikely to change. The above standard conforming code is not difficult to understand, or to write, or for the compiler to understand.

2 Likes

You can also activate Fortran syntax highlighting by writing “fortran” after the initial three backticks.

```fortran
<syntax highlighted code>
```

I think it would be a step backward to require byte addressing in the fortran standard. I have used many word-addressable machines that did not address memory in bytes (and many of those words had bit sizes that were not multiples of 8). I’m not using any of them right now, but who knows what the future will hold. So I prefer this extra level of abstraction that we have in the language now to protect me from any such change in the future.

Back in the 1970s and 1980s, I routinely wrote code with REAL*n declarations. This was nonstandard, but it was the most portable way to write code that compiled, without change, on the wide variety of available hardware at that time. REAL*8, for example, was typically mapped to 64-bit floating point on 64-bit word addressable machines, to 60-bit floating point on 60-bit word addressable machines, and to 72-bit floating point on 36-bit word addressable machines. But that convention was not standard, it was only a vendor-supported convention, and it always felt like an ugly hack. I would have no desire at all to go back to that approach now.

The other part of your post involves the meaning of lhs=rhs expressions in fortran. To me, this is a completely separate issue from requiring byte addressing in the fortran standard.

2 Likes

Probably a dozen of times, yes :slight_smile:

And then you have the IEEE 16 bits floating point, and the BFLOAT16 (Brain Float 16 bits): if you type REAL*2 or REAL(2) in a code, which one is it supposed to be?

Is that really a valid question ?
Does any compiler offer both alternatives in the one .exe file ?
How many Fortran compilers offer either 16-bit real format ?
How would you differentiate between the two if you were using Selected_real_kind ?

I would expect, as with all other uses of Selected_real_kind, you would have to tune your precision and range values to get the answer you actually want.
Does anyone start from the position of I want x precision so what real kind do I use ?

I never used F90+ on a Vax that supported double real to experience how Selected_real_kind solved this selection problem before. I think you would find it is addressed via a compiler option, which is not part of the Fortran code.

The point is not about if some compilers support both at the same time, but if it could happen and it would be desirable: and the answer is yes and yes. Thanks to the kind system there’s no more need to use compile switches to select a variant, it can be done in the code, which is a far better practice. The IEEE fp16 and BFLOAT16 formats have different use cases, and have both in the same code could make sense.

Nonetheless, I agree that the selected_real_kind() mechanism is definitely not perfect and not well suited to selecting between such kinds. But that’s a separate issue that does not justify throwing the baby out with the bath water.

The DEC VAX was a perfect example of this in the 1980s. It supported two different 64-bit floating point formats, but only through compiler options. It was not possible to have the two different kinds in the same program. Ironically, DEC strongly opposed the adoption of fortran 8x during that time, so instead of being the first example of a compiler that supported multiple formats of the same storage size, it instead never supported a f8x or f90 compiler on its VAX machines at all. DEC did partially support multiple fp formats on its later ALPHA hardware in the 1990s, but only through conversions, not through the flexible KIND system. I always thought this was a lost opportunity not only for DEC, but for fortran in general – that would have really showed the power of the language and the power of the hardware. The VAX also had an excellent debugger, based on hardware support that was not available on other CPUs at that time or since.

Although I can’t find any past documentation about that, I’m almost sure that I used in the past a version of the IBM xlf compiler that was supporting both the IEEE and the IBM legacy floating point formats, with different kind values.

I missed April Fool’s Day. Showing someone how straight-forward it is to initialize a non-default-kind float would have been a good one. Even not using the compiler options it is pretty funny …

open ha in Fortran Playground

example of way too many ways
module kinds
implicit none
private
real*8 :: dummy
integer, parameter, public :: wp = kind(dummy)
end module
program haha
use iso_fortran_env , only : wp=>real64, real64
use kinds, only : k_wp=>wp
implicit doubleprecision (a-h)
implicit real(real64) (m-z)
DOUBLE PRECISION :: PI_A=3.14159265358979323d0        ;namelist /pi/PI_A
DOUBLEPRECISION PI_B                                                             
data PI_B/ 3.14159265358979323d0 /                    ;namelist /pi/PI_B
real(8) :: pi_C = 3.14159265358979323d0               ;namelist /pi/PI_C
real*8 :: pi_D  = 3.14159265358979323d0               ;namelist /pi/PI_D
real(kind=8) :: pi_E = 3.14159265358979323d0          ;namelist /pi/PI_E
integer, parameter :: r8=selected_real_kind(15,9)
real(kind=r8) :: pi_F=4.0_r8*atan(1.0_r8)             ;namelist /pi/PI_F
real(kind=wp) :: pi_G= 3.14159265358979323_wp         ;namelist /pi/PI_G
                                                      ;namelist /pi/PI_H
character(len=*),parameter :: pie=&
'3.14159265358979323846264338327950288419716939937510582097494459230&
8164062862089986280348253421170679821480865132823066470938446095505&
2231725359408128481117450284102701938521105559644622948954930381964&
2881097566593344612847564823378678316527120190914564856692346034861&
4543266482133936072602491412737245870066063155881748815209209628292&
4091715364367892590360011330530548820466521384146951941511609433057&
7036575959195309218611738193261179310511854807446237996274956735188&
7527248912279381830119491298336733624406566430860213949463952247371&
0702179860943702770539217176293176752384674818467669405132000568127&
4526356082778577134275778960917363717872146844090122495343014654958&
3710507922796892589235420199561121290219608640344181598136297747713&
9960518707211349999998372978049951059731732816096318595024459455346&
0830264252230825334468503526193118817101000313783875288658753320838&
4206171776691473035982534904287554687311595628638823537875937519577&
18577805321712268066130019278766111959092164201989'
character(len=:),allocatable :: not_a_parameter
not_a_parameter=pie
read(not_a_parameter,*)pi_h ! at least no suffix is needed!
write (*,pi) 
end program haha

The vast majority of calls to selected_real_kind() for common value ranges results in the same thing as real32 or real64 so it seems like overkill but is the most powerful method. No matter what you use to generate the kind if you use it to declare your own kind descriptor like “wp” and use that, then you can change just one line or two anyway; so no matter what syntax you use map it to your own name. In general I think a new user would find it most simple to do something like “integer,parameter :: wp=kind(0.0d0)” and use selected_real_kind or ieee_selected_real_kind as their use of Fortran evolves
`

nice method

``fortran
module answer__real_kinds
implicit none
private
! make a module and/or place definitions at top of a module or in procedures, up to you;
! but really nice to define something however you want in a global area and then use your kind name everywhere else
! the important part is then you probably just have to change the definition in the global area to change the routines.
! you can easily create a generic routine this way, by just defining “wp” to different kinds and then using an INCLUDE
! of the body of the text as well, for a simple templating method.

! so you can use this theoretically powerful Fortran feature and hide it from all the rest of your code if you like,
! which is arguably the best practice
integer, parameter :: minimum_digits_of_precision = 15
integer, parameter :: minimum_exponent_range = 40
integer, parameter, public :: rp15 = selected_real_kind(minimum_digits_of_precision, minimum_exponent_range )
! system double precision
integer, parameter, public :: dp = kind(0d0)
end module answer__real_kinds
program tryit
use answer__real_kinds, only: wp => rp15, dp
implicit none
real(kind=wp) :: pi = 3.14159265358979323846264338327950288419716939937510582097494459230_wp
real(kind=dp) :: pi2 = 3.14159265358979323846264338327950288419716939937510582097494459230_dp
character(len=), parameter:: column = ‘(19(“.”),t1,g0," ",t21,g0)’
write (
, column) ‘PI’, pi
write (, column) ‘REAL(PI)’, real(pi)
write (
, column) ‘DBLE(PI)’, dble(pi)
write (, column) ‘RADIX’, radix(pi)
write (
, column) ‘RANGE’, range(pi)
write (, column) ‘PRECISION’, precision(pi)
write (
,‘(80(“-”))’)
! VERY likely doubleprecision and rp15 are the same
write (, column) ‘PI2’, pi2
write (
, column) ‘REAL(PI2)’, real(pi2)
write (, column) ‘DBLE(PI2)’, dble(pi2)
write (
, column) ‘RADIX’, radix(pi2)
write (, column) ‘RANGE’, range(pi2)
write (
, column) ‘PRECISION’, precision(pi2)
write (*,‘(80(“-”))’)
end program tryit

results of “nice method”:

PI ................ 3.1415926535897931
REAL(PI) .......... 3.14159274
DBLE(PI) .......... 3.1415926535897931
RADIX ............. 2
RANGE ............. 307
PRECISION ......... 15
--------------------------------------------------------------------------------
PI2 ............... 3.1415926535897931
REAL(PI2) ......... 3.14159274
DBLE(PI2) ......... 3.1415926535897931
RADIX ............. 2
RANGE ............. 307
PRECISION ......... 15
--------------------------------------------------------------------------------

LLVM Flang does.

How many are required before the usage of REAL*2 a bad idea?

selected_real_kind(3, 4) should return the kind for 16 bit IEEE float if it’s supported. selected_real_kind(2, 37) should return the kind for BFLOAT16.
With compilers that don’t support those types, those calls would return REAL32.

If you know the types you want, you can use the constants in iso_fortran_env and not bother with selected_real_kind.

select_real_kind(3f) is a powerful flexible feature that I never need.

It does not enforce the limits, it just looks for a size that is
sufficient to meet the parameters; which very often maps to the same
kinds as kind=real32 and kind=real64.

So if I ask for 9 digits of precision I am likely to get 15. That is, if I
used select_real_kind(9,9) (on any machine I have used) that request mapped
to a 64-bit value with select_real_kind(15,307). so if I would actually
like to always get at least what I developed with, I am safer if I use
select_real_kind(15,307) (which is very likely to be the same as real64!).

I might use kind=real16 in the future and when I do I will probably
use select_real_kind(3f) and be glad it is there, but in the meantime
the bit-size requests are much simpler to use and map to the same few
choices on anything I have been running on lately.

If you query your programming environment you will probably find it
maps all the many valid values of select_real_kind(3f) to three or four
kinds that are all that are available for a particular compiler. Very
likely only two sizes will be of interest for reasons of performance or
portability. It will be a surprise if they are not the same as kind=real32
or kind=real64.

There are very good reasons to introduce a new programmer to defining a
kind using their own mneumonic but they usually find using kind suffixes
on all constants being a “good practice” odd enough, so I usually just
recommend coding using something like

 integer,parameter :: sp=kind(0.0), dp=kind(0.0d0)

or
integer,parameter :: sp=real32, dp=real64

and then in their code defining a working precision, perhaps like

 integer,parameter :: wp = dp

But my biases aside, this little program might be instructive. It
writes another program that writes a select_real_kind(3f) statement
for each available floating kind a compiler supports.

program srk
use iso_fortran_env, only: real_kinds
use, intrinsic :: iso_fortran_env, only : compiler_version
implicit none
character(len=*), parameter :: g = '(*(g0))'
integer :: i, j
   write (*, g) 'program sizes'
   write (*, g) 'use iso_fortran_env, only : real_kinds'
   write (*, g) 'implicit none'
   write (*, g) "character(len=*),parameter :: g='(*(g0))'"
   do i = 1, size(real_kinds)
      write (*, g) 'real(kind=', real_kinds(i), ") :: r", real_kinds(i), '=0.0_', real_kinds(i)
   end do
   print '(3a)', 'write(*,g)"! ', compiler_version(),'"'
   do i = 1, size(real_kinds)
      j=real_kinds(i)
      write (*, g) 'write(*,g)', &
        '"integer,parameter :: wp=select_real_kind(', &
        'p=",precision(0.0_',     j,  &
        '),",r=",range(0.0_',     j,  &
        '),",radix=",radix(0.0_', j,  &
        '),")" &', new_line('a'), &
        '," ! storage size=",storage_size(0.0_',j,')', &
        '," kind=",', j
   end do
   write (*, g) 'end program sizes'
end program srk

If you run it and compile the resulting program source with the same
compiler you will get results like the following. The kind=10 from the
gfortran(1) compiler shows why you could be missing out if you are not
using select_real_kind(3f), but it generally shows there are really only
a few choices and that now-adays they are very similiar or the same between
platforms.

if you really want to capture what you have developed your code with the
program shows the statement you need to change to a select_real_kind(3f)
statement that will give you at least the precision and range you
developed with or fail so you know you will be running with untested
precision or range.

gfortran srk.f90 && ./a.out >_xx.f90 &&gfortran _xx.f90 && ./a.out
! GCC version 13.1.0
integer,parameter :: wp=select_real_kind(p=6,r=37,radix=2) ! storage size=32 kind=4
integer,parameter :: wp=select_real_kind(p=15,r=307,radix=2) ! storage size=64 kind=8
integer,parameter :: wp=select_real_kind(p=18,r=4931,radix=2) ! storage size=128 kind=10
integer,parameter :: wp=select_real_kind(p=33,r=4931,radix=2) ! storage size=128 kind=16
ifx srk.f90 && ./a.out >_xx.f90 &&ifx _xx.f90 && ./a.out
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.2.0 Build 20230721
integer,parameter :: wp=select_real_kind(p=6,r=37,radix=2) ! storage size=32 kind=4
integer,parameter :: wp=select_real_kind(p=15,r=307,radix=2) ! storage size=64 kind=8
integer,parameter :: wp=select_real_kind(p=33,r=4931,radix=2) ! storage size=128 kind=16
2 Likes