Integer 4 or integer 8?

Dear all,

I have a quick question, do you use integer 4 or integer 8?

For example, I define my integer 4 as

integer (kind=i4)

and integer 8 as

integer (kind=i8)

where

integer, private, parameter :: i4=selected_int_kind(9)
integer, private, parameter :: i8=selected_int_kind(15)

While np and nd are all integer 4 type, np*nd can be big enough can become integer 8 type. So if I need a variable jjj to represent np*nd, probably I need to define jjj as integer 8,

integer(kind=i4) :: np,nd
integer(kind=i8) :: jjj
jjj = np*nd

I mean if I have integer 4 and integer 8 types, I need to be careful enough and make sure when the product of integer 4 becomes big enough and requires integer 8. It is OK to use minimal data type in this way, but occasionally it may not be the most convenient perhaps.

So I wonder, how do you guys deal with such situation?
Do you just use integer 8 everywhere or something?

I found using integer 8 everywhere is perhaps not the most convenient either, and may very slightly slow down the code. So I am not exactly sure what is the best approach.

Thanks much in advance!

Most of the time, I just use the default kind, which I know will be at least 4 bytes on PC:

integer :: i

If I know or suspect that the value may become big (>2^31), I use integer(int64) (defined in iso_fortran_env). And int8 (8 bits) or int16 may be useful if memory matters (big integer arrays).

Considering speed, I am not sure int64 will be slower on nowadays 64 bits CPU.

1 Like

In the original version of OP there was an array AAA(np,nd). I guess that internally, the processor should deal properly even with AAA(100000,100000) although the indices would overflow when simply multiplied.

In explicit calculations, however, one has to make sure there is no overflow and use proper kind(s). Note also, that with your declarations:

integer(kind=i4) :: np,nd
integer(kind=i8) :: jjj
jjj = np*nd

jjj will not be properly assigned if np*nd overflows in i4 kind. Consider sample program:

program main
  use iso_fortran_env, only: i4=>int32, i8=>int64
  integer(i4) :: i=100000, j=100000
  integer(i8) :: bi,bj
  bi = i*j              ! overflows, assigns bad value
  bj = int(i,kind=i8)*j ! converted to i8 before multiplication
  print *, bi, bj
end program main
! outputs:    1410065408       10000000000
1 Like

On WSL2 compiling the code above with gfortran -g -ftracer -ftrapv int_overflow.f90 and running I get

(base) /mnt/c/fortran/test$ ./a.out

Program received signal SIGABRT: Process abort signal.

Backtrace for this error:
#0  0x7f99f6416700 in ???
#1  0x7f99f64158a5 in ???
#2  0x7f99f622e20f in ???
#3  0x7f99f622e18b in ???
#4  0x7f99f620d858 in ???
#5  0x7f99f63dea41 in ???
#6  0x55db6d14a1b8 in MAIN__
	at /mnt/c/fortran/test/int_overflow.f90:5
#7  0x55db6d14a297 in main
	at /mnt/c/fortran/test/int_overflow.f90:8
Aborted

I use plain integer in my codes but should probably compile with -ftrapv to ensure that I am not missing integer overflow.

1 Like

Sure if you add -ftrapv, signed overflow will cause exception. But w/o it, gfortran (ifort as well) produces code that silently ignores overflow giving bogus results. For ifort there seems to be no equivalent of -ftrapv. For other compilers I do not know.

2 Likes

Thank you very much @vmagnin @msz59 @Beliavsky !
How about simply just use integer 8 everywhere? Is there any drawback?

I do not think any significant slowdown can be possible on 64-bit machines, 64-bit code. Unless your huge arrays (such that np*nd>2G) are integer also. Then you’ll get memory requirements really bigger.

1 Like

Thank you @msz59 , your bi = i*j illustration is indeed great! Thank @Beliavsky too!
I did not realize that will cause an overflow, since bi on the left-hand-side is integer 8, I assume i*j should automatically be integer 8 and is calculated correctly.
But it seems it is not that intelligent and I need to be careful. Probably I may just use integer 8 instead.

A general rule of Fortran is that the RHS of an assignment is computed independently of what is on the LHS and then converted to that type. The product of two default integers is always a default integer.

1 Like
  1. I am too lazy to write unnecessarily more than integer :: and the code looks nice and simpler that way… :slightly_smiling_face:
  2. I am too old to waste 4 bytes without reason. I learned BASIC in the early 80’s on pocket computers with 1024 bytes RAM… Moreover, in the 90’s 32 bits integers were faster than 64 bits… :grin:
3 Likes

The times have changed, grandpa … :wink:

2 Likes

If anything, they have changed to make 32 bit integers more attractive. Data movement is what you pay for in time and energy and heat. If 32 bits are enough, it would be daft not to use them.

1 Like

is there any consensus in the community to compile a program with a default integer size of 4 or 8?

I work with an app that heavily relies on default being 8 whereas I am working on writing a library and I want to use best practices.

There is a strong concensus to use ‘IMPLICIT NONE’, which requires each variable to be part of a declaration. Since everything has a declaration it is not much effort to use a KIND on a declaration
to choose the appropriate size. In general, using an integer value directly as a kind (the meaning of the numbers is up to the compiler and is not specified by the standard) is discouraged. Probably SELECT_INT_KIND() is the best method in some regards, but not really for procedure arguments. You can also use names like INT32, INT64 which are defined in the standard. For arguments it is important to sometimes support more than a single kind. You can do this with generic procedures. Hopefully you can use templates in the future which reduces the duplication. Since it is not trivial unless you use a preprocessor or INCLUDE to minimize the code duplication do not support every kind and type there is for every procedure.

If you do want to make the default different and not use implicit none use implicit. Depending on compiler switches is the worst choice, as it is not clear from the source code alone what kinds are required.

3 Likes

I find the main argument against using a nondefault kind everywhere is that it makes it difficult to match actual and dummy arguments. For example, if you are using a standard library such as BLAS or LAPACK, its dummy integer arguments are almost certainly compiled with the default integer kind (usually int32), so every time you use a subroutine you will need to make copies, in and out if necessary (for intent(inout) or for unspecified intent), or do explicit conversions (for intent(in)). Also, these libraries often do not have an explicit interface (e.g. they are not in modules), so the compiler does not catch the argument mismatches for you, you must do it manually or with interface blocks. All of that becomes tedious and clutters the code. The LAPACK code in particular is under active development, with new capabilities and techniques added all the time, so it is not just a simple matter to make local copies of the routines within a local module, your local copies then risk becoming obsolete relative to the latest source distribution. And after some four decades, it appears unlikely that the LAPACK developers are going to change conventions and use these modern features of the language to support the various integer and real kind values.

4 Likes

I think there is a consensus to NOT use the compilation options to promote the default integer to a higher size, unless there is a very good reason to do so. The very good reason is most of the time (always) a legacy code that relies on the assumption that the default integer is an integer*8. But this is a workaround, not a good solution.

4 Likes

Hi @PierU thanks for the direct response!

Yeah, I am working with a legacy app and redesigning a backend for it in an attempt at modernizing it. Great thing I asked!

To me, the question should be is what integer kind should be the default for a 64-bit Fortran compiler ?
With 64-bit OS examples, such as the intrinsic function size defaulting to the default integer and producing rubbish results, this outcome is not fit for purpose if 4 (actually int32) remains the default integer.

Hopefully a future Fortran standard will address what default integer is suitable for a 64-bit Fortran.

1 Like

There are two constraints here,

  • Fortran requires that the default integer and real have the same storage size. If the default integer were 64-bit, then double precision would be 128-bit and would end up emulated in software. I don’t see the necessary user pressure to get hardware-quad, if anything, we are moving in the opposite direction, where more hardware will drop double precision.
  • Fortran implementations are joined at the hip to C and C++. You can’t change default Fortran integers to 64-bit, if lots of system software and C libraries are using 32-bit int.

It’s worth keeping in mind the windy path taken to reach the currently dominant LP64 model:

1 Like

This is a ridiculous approach. If this is not fit for purpose for 64-bit memory addresses, then the Standard should be updated, rather than constrain Fortran’s future use.