What are the true portable or best to define real 4 real 8 integer 4 integer 8, etc?

Dear all,

I know this may be a very basic question. But I wanted to ask, what are the truly portable or best way to define real 4, real 8, int 4, int 32, etc?

I mean like, I usually do,

integer, public, parameter :: i4=selected_int_kind(9)
integer, public, parameter :: i8=selected_int_kind(15)
integer, public, parameter :: r8=selected_real_kind(15,9)

Then I use things like

integer(kind=i4) i
integer(kind=i8) iseed
real(kind=r8) :: abc

Question,

  1. If you use select kind, how do you specify what is integer 4, integer 8, real 8, etc?

  2. Or is there better to just use iso_fortran_env?
    For example, i found a code using that for the ziggurat random number generator,
    ecosim/ziggurat.f90 at main · sandain/ecosim · GitHub

There was that discussion in 2020:

@sblionel is pleading for selected_real_kind()

Personally, I now use iso_fortran_env, which is sufficient for my simple needs (computing on a PC).

1 Like

The answer depends on what you mean by portable real 4/8 etc. If you need the specific size in bytes/bits, selected_XXX_kind are not the best option as they’ll silently return bigger kinds if smaller are unavailable (you can, however, check this using storage_size() intrinsic). For that purpose the parameters intXXX and realXXX from iso_fortran_env seem to serve better, although you’ll get compiler error if any of those does not exist in a given implementation (negative values).

Such a strict size requirements may occur if you need to read binary data or, less probably, use a binary-only library expecting arguments of given size. You can probably expect that every implementation of Modern Fortran today has integers and reals both in 4 and 8 byte sizes, although the standard does not guarantee that, I guess. I used to think that Cray Fortran had default real of 8 bytes but apparently it is not true.

Reading binary data smaller than the smallest available kind would be non-trivial, especially for real values. Same for using a binary library. For integers, in little endian architecture, you could probably cheat such library using bigger data objects (with properly low values, of course).

1 Like

I use iso_fortran_env and create short forms i8 => int8, i16 => int16, i32 => int32, i64 => int64, r32 => real32, r64 => real64.

That being said, we’ve run into a situation at work where we are using a 32-bit signed integer as an ID type, and our simulations are getting larger than 2 billion elements, which causes all sorts of unexpected errors. Using selected_int_kind() would be useful there. If we had created an integer kind like this:

integer, parameter :: object_id = selected_int_kind(9)

Then we could have easily changed it to:

integer, parameter :: object_id = selected_int_kind(11)

And everything would have automatically been updated to support the larger range.

2 Likes

@CRquantum and anyone else similarly interested, the time may be now to start employing Fortran stdlib more and more in your work starting with stdlib_kinds:

There is no need really to reinvent the wheel on this matter anymore, you should consider simply using

   use stdlib_kinds ..
1 Like

Depending on the options chosen, that file could be

module stdlib_kinds
  use iso_fortran_env, only: int8, int16, int32, int64
  use iso_c_binding, only: c_bool
  implicit none
  private
  public :: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool

  !> Single precision real numbers
  integer, parameter :: sp = selected_real_kind(6)

  !> Double precision real numbers
  integer, parameter :: dp = selected_real_kind(15)

  !> Extended double precision real numbers
  integer, parameter :: xdp = selected_real_kind(18)

  !> Quadruple precision real numbers
  integer, parameter :: qp = selected_real_kind(33)

  !> Default logical kind parameter
  integer, parameter :: lk = kind(.true.)

end module stdlib_kinds

With the driver

program main
use iso_fortran_env, only: compiler_version
use stdlib_kinds
implicit none
print*,trim(compiler_version())
print "(*(a6))","sp","dp","xdp","qp","lk"
print "(*(i6))",sp,dp,xdp,qp,lk
end program main

sample output is

 GCC version 12.0.1 20220213 (experimental)
    sp    dp   xdp    qp    lk
     4     8    10    16     4
 Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel
 (R) 64, Version 2021.5.0 Build 20211109_000000
    sp    dp   xdp    qp    lk
     4     8    16    16     4
2 Likes

The exact way you do this depends on the situation. If you are trying to match precisions in a specific library, then you would do things differently than, for example, if you are writing your own code from beginning to end with some precision requirements. Sometimes you want to target some specific hardware. Other times you want to write portable code that runs, as much as possible, the same way on a wide range of hardware the software combinations. The important thing is that you specify the precisions in one place in a module, and then let that definition propagate throughout the rest of the code. Then in that module you can use selected_real_kind, or fortran_env, or kind(1.d0), or c interop, or whatever is appropriate.

2 Likes

@CRquantum and anyone else similarly thinking about portability,

TL;DR:

  • use ISO_FORTRAN_ENV for intrinsic types other than REAL,
  • Either use stdlib_kinds for REAL type or consider IEEE_SELECTED_REAL_KIND from IEEE_ARITHMETIC intrinsic module in the Fortran standard.

If you are serious, take a bit to reflect on this and ask yourself if you ever anticipate the codes of interest to you - the ones you author and the other ones you or your customers use - will ever run on hardware other than those employing IEEE floating-point arithmetic. Chances are rather high the answer is no.

Practically every single machine in academia, research, industry, and personal needs that you will use can be expected to do floating-point computations using IEEE arithmetic.

Under the circumstances, there is really no need to sweat further on details other than to ensure consistency with a good base. Fortran stdlib_kinds provides that. For whatever reason, if that is unusable or unsatisfactory, look into IEEE_SELECTED_REAL_KIND in the Fortran standard.

   use, intrinsic :: iso_fortran_env, only : .. I4 => int32, I8 => int64, ..
   use, intrinsic :: ieee_arithmetic, only : .., ieee_selected_real_kind, ..
   ..
   integer(I4) :: n
   ..
   integer, parameter :: WP = ieee_selected_real_kind( p=.. )
   ..
   real(WP) :: x

As to what to use for the arguments P (precision in decimal digits) [and R (range), RADIX], you can consult the ISO/IEC/IEEE 60559:2011 standard or ask here but know that supplying only the precision (P) is adequate.

And that for IEEE binary64 format, the most commonly used format for the so-called double precision floating-point representation, the Fortran compilers will all yield the right kind if *SELECTED_REAL_KIND intrinsic function is used with only P=15.

1 Like

Decimal arithmetic may be coming soon to hardware near you, so you might want to start thinking about whether you want to specify RADIX as well in the reference to SELECTED_REAL_KIND/IEEE_SELECTED_REAL_KIND.

1 Like

Maybe.

But the really unfortunate situation in the world of Fortran is any and all processor-dependent facilities - decimal arithmetic is clearly one such - are perennially n + x years away, where both n and x are unknown even if understood to be >5 and either of them can tend toward infinity.

I won’t hold my breath for OP, or several generations after OP in their PhD program, to be able to perform any Fortran-based computations of any scientific or technical merit in their lifetimes.

But I always eagerly look forward to being proven wrong.

1 Like

While on most, if not all, platforms it amounts to the same thing, I’m rather surprised this isn’t sp = kind(1.0) and dp = kind(1.0d0). That would seem to be more consistent with what the standard regards as “single” and “double precision”. Anybody recall the rationale for this choice?

2 Likes

I agree with @nncarlson. Suppose there is an implementation with 64-bit default REAL and 128-bit DOUBLE PRECISION - I guess that wouldn’t violate the standard, would it? Then the definitions from stdlib would give the same kind for both sp and dp.

1 Like

Thanks @nncarlson .
I have a very stupid question, if real 8 or double precision kind is defined as
dp = kind(1.0d0), then I can define a real 8 variable, say AAA as,

real(kind=dp) :: AAA

However since dp is just the kind of 1.0d0, and 1.0d0 is double precision, right? Then why not just use

double precision :: AAA

Sure, you can if you’d like. But you shouldn’t assume it is the same thing as an 8-byte IEEE real, because the standard doesn’t prescribe that. If you want portable ways to define integers and reals of specific byte sizes (one of your original questions) then I think that is pretty clearly to use the named constants from iso_fortran_env.

1 Like

With declarations of the form real(kind=dp) :: x with dp defined in a module, you can set dp to real128 if you think your program is giving wrong results due to insufficient precision. If you have declarations with double precision in many places, changing all the reals to another precision takes much more work.

1 Like

As hinted by @vmagnin , I expressed my thoughts regarding this topic at Doctor Fortran in “It Takes All KINDs” - Doctor Fortran (stevelionel.com)

2 Likes