Discussion on Fortran's type-kind distinction

Having come to Fortran from a C/C++ background (mainly), I was originally confused and annoyed by Fortran’s distinction between type and kind. I’ve since realized that it has several merits (as well as introducing some complications), but I’d like to hear opinions and experiences regarding that system from more experienced Fortranners than myself. Do you find it to be a better design than C-style types (with no ‘kind’ concept)? Or just an annoying quirk, present for “legacy reasons” that we now have to deal with? Please explain.

I’ll start: I think the ability to specify the numerical properties of the types you want (i.e. selected_real_kind and so on) is an interesting asset to portability. For example, where an algorithm can get away with low-precision floating point math, selected_real_kind allows you to write code that could use 16 bit floating point on hardware with support for such a type, or default to the more common 32 bit floating point on hardware without such support. However, it also makes writing portable libraries more complicated, as has been pointed out by several prominent members of this forum.

1 Like

I have always been against “selected_real_kind” mainly because of the question it asks is not related to the hardware real formats available.

It asks the question of what precision you want to use, but typically, providing the number of digits required is not an easy question to answer, given the computation algorithm to be used.

The other main objection I have relates to what are the options available, which are the different real formats that are supported. These are now really 4-byte or 8-byte reals, while 10-byte or 16-byte are not typically a viable option. (neither is 4-byte !)
However, once you know what digit value you provide will lead to the hardware number formats that are available, you do have control of what is being selected.

Basically;
if you need an 8-byte real then you provide digits = 7 to 15.
if you need an 8-byte integer then you provide digits = 10 to 18.

How many times do you have to check what value of digits is required for the type of variable ?

I have always related precision to what bit size formats are available, even before bytes were standardised.

I don’t think I have ever coded a computation approach in Fortran where I have tested the accuracy of a computed result and changed the number type, then repeated the calculation using generic functions to improve the accuracy.

The other problem for “selected_real_kind” is timing. Prior to 1990 there were many other hardware real formats, but since 1990, most have disappeared, with only the IEEE754 formats remaining. So the main problem that selected_real_kind addressed has disappeared. If code developers in the 60’s to 80’s documented how many bits (or bytes) were in the REAL they used, a lot of these issues would have been mitigated; but they rarely did.

3 Likes

I think the kind type parameters included in the intrinsic module iso_fortran_env make it more straightforward to deal with different kinds of variables. They make it easy to get the right kinds.

iso_fortran_env in Fortran Wiki

Small snippet from: Variables - Fortran Programming Language

program float
  use, intrinsic :: iso_fortran_env, only: sp=>real32, dp=>real64
  implicit none

  real(sp) :: float32
  real(dp) :: float64

  float32 = 1.0_sp  ! Explicit suffix for literal constants
  float64 = 1.0_dp

end program float
4 Likes

Is it really so that C does not have kind concept? Imagine the following hypothetical C syntax:

int(kind=long) i,j;          // long int i,j; 
int(kind=short) h,g;         // short int h,g;
float(kind=double) x,y;      // double x,y;
1 Like

As far as I know there’s the header <stdint.h> that contains type definitions for different “kinds” of integers in C. It is very useful in the same way as iso_fortran_env in that it allows a programmer to define an integer with exact number of bits.

https://www.gnu.org/software/libc/manual/html_node/Integers.html

2 Likes

I wonder if selected_real_kind was addressing the problem from the 60s, 70s and early 80s, that has disappeared by the time it became available in the standard and compilers.

Now, can it happen in the future that we will see more variety again? I think it can. We might have both half precision (real16?) as well as bfloat16.

What is nice about the selected_real_kind approach is that it is hardware independent. You select the properties of floating point that you need, and your code should run on any (future) hardware. So the idea is good. But it’s pain to type (and remember!) the correct ranges for double and single precision.

So in practice, I think we need to do what stdlib is trying to address with its kinds module: stdlib_kinds.f90 – Fortran-lang/stdlib, where it exposes sp, dp, qp kinds and we can add different kinds for half and bfloat in the future if needed.

It seems the intrinsic iso_fortran_env is perhaps addressing exactly the same issue, but there seems to be confusion about the purpose of it. One approach is that it only determines the size of the floating point based on bits (such as 32 or 64), so it is (or will be in the future) unable to distinguish real16 and bfloat16. Another approach is that iso_fortran_env lists simple names for all commonly used floating point formats, and it will simply add bfloat16 if it is used in hardware a lot, as well as any other such format.

The way it can work then is that if a code uses real32 or bfloat16 (in the future) from iso_fortran_env, it could ensure that exactly this type or a wider type will be used. Except I believe a compiler will return -1 if the exact kind is not present.

So it seems the best of both worlds is to have the kinds module in stdlib, but instead of iso_fortran_env, it would use selected_real_kind with the proper ranges, which would ensure that say hp (half precision) or bp (bfloat16) is either that type, or a larger type, thus ensuring Fortran code keeps running.

Here is another issue: say you write code that works with single precision (just as an example) and that uses epsilon and you tune the iterations and everything to work. Then the compiler ends up using double precision (just as an example), as permitted by selected_real_kind. Will epsilon suddenly drop from 1e-8 to 1e-16? If so, that can screw up the algorithm for example it can get a lot slower if you tuned it to just get single precision correctly. What is the way to fix this problem?

2 Likes

To me kinds seem like a incomplete solution made in a world where generics don’t exist. With generics, you can just write the program for any subtype of number and let the user choose which one they want.

1 Like

But how would you define those subtypes in generics w/o kinds?

1 Like

So in Julia, you can write

function mysum(A::Array{T,N}) where {T<:Number, N}
    result = zero(T)
    for x in A
        result += x
    end
    return result
end

This function works for any subtype of number. For a basic example,

struct mynumber <: Number
    val :: Float64
end
Base.+(a::mynumber, b::mynumer) = mynumber(a.val+b.val)

I have just defined an (admittedly stupid) custom number type, but mysum will accept an Array of mynumber without any problems. This is why parametric subtypes are necessary for a good programming language for science.

2 Likes

Sorry, I thought you were referring to Fortran generics

1 Like

My biggest issue with the current type/kind system is that virtually all compilers use the number of bytes (4 or 8 etc) used by a particular type as the KIND value returned by the selected_xx_kind functions or the intrinsic parameter values (REAL32, REAL64 etc) AND don’t differentiate between an 8 byte integer or an 8 byte REAL. Specifically, INT32 and REAL32 both have a value of 4, INT64 and REAL64 both have a value of 8. I guess this was selected to make it easy for people who liked to use REAL(8) or REAL*8 etc. I see no reason for this. The value of a KIND should be irrelavant. The only thing that matters is that REAL32 and REAL64 have different values and that INT32 should not be the same value as REAL32,etc. On the surface, a straightforward fix is to assign types to different ranges of KINDs. Ie INT32 =14, INT64=18, REAL32=24, REAL64=28 etc. and you have to believe that compiler developers are skilled enough programmers to write logic to allow both REAL(8) and REAL(REAL64) (with REAL64 having a value of something other than 8) to coexist in the compiler.

This matters to me for two reasons.

  1. In (I think) Fortran 2008, you are allowed to use the following form of TYPE to select intrinsic KINDS

    TYPE(REAL(REAL64)) :: A which makes this construct redundant and serves no real purpose that I can see. I guess the REAL(REAL64)) is required because INT64 and REAL64 both have the value of 8 in most compiler implementations. If INT64 and REAL64 had different values then one could just use TYPE(REAL64) :: A which makes it potentially more useful for writing generic code.

  2. This also would make writing truly generic, template like containers for things like lists of intrinsic values using PDTs (if the developers ever get them to work as designed) a lot easier.

Example:

Type :: list_value(ltype)
   Integer, KIND :: ltype
   Type(ltype) :: lval
   Type(list_value(ltype)), pointer :: nextp
End Type
Type :: genlist(ltype)
   Integer, KIND = ltype
   Type(list_value(ltype)), pointer :: firstp
Contains
 ! list methods
End Type

Type(genlist(REAL64)) :: r8list
Type(genlist(INT32)) :: i4list

I know that the same thing can be done with unlimited polymorphism but in my experience CLASS * is the single biggest generator of ICE errors in almost all compilers. As a side note I’ve always felt introducing the CLASS keyword into the language was a mistake. I view polymorphism as an ATTRIBUTE of a derived type and would have implemented it as an attribute. ie

Type(alist), POLYMORPHIC :: list

Plus we could have just TYPE() instead of the currently confusing CLASS() and TYPE(*).

Edit:

I see this as being more in line with implementing a construct for static (compile time) polymorphism since you have to set the KIND parameter at compile time.

I realize that its too late to change KIND along the lines that I suggest as long as the standards folks adhere to their “We can’t break existing code” mantra (although I challenge them to show me a case were if KIND parameters are used as designed the proposed change would break code). I see this as just another example of the standards folks thinking too much about preserving the past instead of preparing for the future

just my 2 cents

2 Likes

One place were this is useful - using derived types that implement arbitrary or higher precision numbers (e.g. double double), or automatic differentiation using dual numbers through operator overloading.

The library in the link offers a derived type called dual that supports most of the operations that reals do, while also keeping track of the first derivative through the chain rule.

The dual numbers come handy when performing parameter fitting and numerical optimization of mathematical models. After I’ve found the parameters or optimum of my model, I’d like to evaluate the function without the performance penalty of the dual numbers.

The type syntax you just mentioned, makes templating (a bit) easier in such cases:


#:set abbrv = ['rsp', 'rdp', 'dual']
#:set types = ['real(sp)', 'real(dp)', 'dual']

#! Collect tuples of abbreviation and type
#:set abbrv_types = list(zip(abbrv,types))

interface sin2
#:for ab in abbrv
  module procedure sin2_${ab}$
#:endfor
end interface sin2

#:for ab, t in  abbrv_types
function sin2_${ab}$(xx) result(res)
  type(${t}$), intent(in) :: xx
  type(${t}$) :: res

  res = sin(xx) * sin(xx)

end function
#:endfor
2 Likes

Explicit kinds are also useful for interoperability with other languages. An example.

2 Likes