Is this expected? Fortran standard is not respected by `gfortran --fdefault-integer-8`, `ifort -i8`, or `nagfor -i8`

I would like to draw your attention to a discussion here: fortran - Bug? MATLAB MEX changes the kind of the default logical - Stack Overflow

In brief, even though Fortran standard 2018 requires that ieee_is_nan should return a default logical, we will have kind(ieee_is_nan(1.0) /= kind(.false.) with gfortran --fdefault-integer-8, ifort -i8, or nagfor -i8. Assuming that the constant .false. is a default logical, we find that the compilers violate the Fortran standard.

A minimal working example is as follows.

! test_kind.f90

program test_kind

use, intrinsic :: ieee_arithmetic, only : ieee_is_nan
implicit none

write (*, *) 'kind(ieee_is_nan(0.0)) = ', kind(ieee_is_nan(1.0))
write (*, *) 'kind(.false.) = ', kind(.false.)

end program test_kind

Name this piece of code as test_kind.f90. The following is what happens on my computer (Ubuntu 20.04, Intel(R) Core™ i7-10610U CPU @ 1.80GHz) when I compile it with a few compilers.

$ gfortran --version
GNU Fortran (Ubuntu 9.3.0-17ubuntu1~20.04) 9.3.0
$ gfortran -fdefault-integer-8 -std=f2018 -Wall -Wextra test_kind.f90 
$ ./a.out 
 kind(ieee_is_nan(0.0)) =                     4
 kind(.false.) =                     8
$ ifort --version
ifort (IFORT) 2021.3.0 20210609
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.
$ ifort -i8 -stand f18 -warn all test_kind.f90 
$ ./a.out 
 kind(ieee_is_nan(0.0)) =                      4
 kind(.false.) =                      8
$ nagfor -v
NAG Fortran Compiler Release 7.0(Yurakucho) Build 7036
$ nagfor -i8 -f2018 test_kind.f90 
NAG Fortran Compiler Release 7.0(Yurakucho) Build 7036
Warning: test_kind.f90, line 5: Incompatible option setting for module IEEE_ARITHMETIC (was not compiled with the -i8 option)
  ...
[NAG Fortran Compiler normal termination, 4 warnings]
$ ./a.out 
 kind(ieee_is_nan(0.0)) =  3
 kind(.false.) =  4
$ flang --version
clang version 7.1
Target: x86_64-unknown-linux-gnu
Thread model: posix
$ flang -fdefault-integer-8 -Wall -Wextra test_kind.f90 
$ ./a.out 
 kind(ieee_is_nan(0.0)) =                         8
 kind(.false.) =                         8

It seems to me that gfortran, ifort, and nagfor all violate the Fortran standard even though the standard is imposed explicitly as a comilation option; the last one remembers to raise a warning whereas the first two are completely happy and stay absolutely silent. flang, in contrast, behaves according to the standard.

Is it considered tolerable for the compilers to violate the standard silently, or should we regard it as a bug?

If you ask whether the behavior described above affects any production code, here is a real-life example.

! test_assert.f90

module assert_mod

implicit none
private
public :: assert


contains


subroutine assert(assertion, description)

implicit none

! Inputs
logical, intent(in) :: assertion
character(len=*), intent(in) :: description

if (.not. assertion) then
    write (*, *) 'Assertion failed: '//description
end if

end subroutine assert

end module assert_mod


!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
program test_assert

use, intrinsic :: ieee_arithmetic, only : ieee_is_nan
use, non_intrinsic :: assert_mod, only : assert
implicit none

call assert(ieee_is_nan(1.0), '1.0 is NaN')

end program test_assert

This piece of code is completely standard-compliant, I hope. Name it as test_assert.f90 and then compile it. This is what happens on my computer.

$ gfortran -fdefault-integer-8 -F2018 test_assert.f90 
test_assert.f90:37:43:

   37 | call assert(ieee_is_nan(1.0), '1.0 is NaN')
      |                                           1
Error: Type mismatch in argument ‘assertion’ at (1); passed LOGICAL(4) to LOGICAL(8)
$ ifort -i8 -stand f18 test_assert.f90 
test_assert.f90(37): warning #6075: The data type of the actual argument does not match the definition.
call assert(ieee_is_nan(1.0), '1.0 is NaN')
------------^
$ nagfor -i8 -f2018 test_assert.f90 
NAG Fortran Compiler Release 7.0(Yurakucho) Build 7036
Warning: test_assert.f90, line 33: Incompatible option setting for module IEEE_ARITHMETIC (was not compiled with the -i8 option)
...
Error: test_assert.f90, line 37: Incorrect data type LOGICAL(word) (expected LOGICAL) for argument ASSERTION (no. 1) of ASSERT
[NAG Fortran Compiler error termination, 1 error, 4 warnings]

So gfortran and nagfor fails to compile it, and ifort complains even though there is nothing wrong with the code according to the standard.

Now someone may say, “you get what you want when playing with dangerous options like -fdefault-integer-8. Take it as a lesson of your life even though you lost your legs because of it”. Sure, but there are some problems.

  1. How do we know which options are dangerous and others are not?

  2. Shouldn’t there be at least a warning when users are “playing with dangerous options”?

  3. Unfortunately, the MATLAB MEX takes -fdefault-integer-8 as the default option when compiling Fortran code using gfortran. So test_assert.f90 won’t be compiled even though there is nothing wrong with the code. This happened in a real-life project. We may blame MEX for enforcing this dangerous option by default, but I guess the programmers at MathWorks did not know that it was dangerous and they simply trusted the compiler vendors.

What is your opinion? Thank you very much for any comments or criticism.

Welcome to the forum. For the first program you presented, compiling with just gfortran or gfortran -std=f2018 gives output

 kind(ieee_is_nan(0.0)) =            4
 kind(.false.) =            4

I think a compiler is standard-conforming as long as it gives the output the standard requires when the standard-conformance option is turned on, and that it has the freedom to give other output when other options are used.

Thank you for your quick response. Unfortunately, the compiler behaves in the same way even if the standard is imposed explicitly. See my updated post.

@zaikunzhang ,

Welcome to the forum!

I reckon you’re dealing with a bug in those 3 compilers with the kind of result with their IEEE_IS_NAN implementations.

The standard is both clear as well as most considerate with the processors:

  • The standard extends the processors (compilers) considerable leeway with their selection of default integer and default logical (and default real),
  • The standard mostly just asks, “a nonpointer scalar object that is default integer, default real, or default logical occupies a single numeric storage unit.”

Thus with the options the processors provide to specify the default integer characteristic, the compilers fail to adapt their IEEE_IS_NAN implementations in accordance with the specified setting (-i8, etc.) even though they do so with the KIND intrinsic. Thus they are inconsistent.

From a practical point-of-view, however, you will likely have to submit separate support requests with each problematic compiler and take it from there.

1 Like

Thank you! I agree with you. I will try to file bug reports to the compiler vendors/developers, maybe next weekend. Meanwhile, as pointed out by @kargl, the problem is not unknown to the gfortran community.

1 Like

For the NAG Compiler, the documentation states it clearly:

https://www.nag.com/nagware/np/r70_doc/manual/compiler_2_4.html#OPTIONS

-i8

Set the size of default INTEGER and LOGICAL to 64 bits. This can be useful for switching between libraries that have 32-bit integer arguments (on one platform) and 64-bit integer arguments (on another platform), but which do not provide a named constant with the necessary KIND value.

This has no effect on default REAL and COMPLEX sizes, so the compiler is not standard-conforming in this mode.

Searching for “standard-conforming” on the same web page will give you all the instances where conformance is affected.

1 Like

It is reassuring to see that nagfor has made clear in the documentation that this option is not standard-conforming. I should have read the documents more carefully. Indeed, nagfor is the only one that warns about this option in my examples. It is clear that the developers at NAG are careful about this option.

Sure. I will do something about it this weekend. Although I am not confident of my C progamming, I should at least use my English to improve the situation. Thank you!

1 Like