`nagfor` 7.1 supports half-precision floating-point numbers, but with many bugs

Half-precision real has been widely available on GPUs with important applications in machine learning. On CPUs, it seems less available.

I discovered just a few days ago that nagfor now supports REAL16, half-precision real. This is very interesting.

However, I found a couple of bugs after a quick try on PRIMA. Here is an example, which has been submitted to NAG confirmed as a bug by NAG.

Code (also available at test_compiler/test_isorth.f90 at master · zequipe/test_compiler · GitHub):

! test_isorth.f90

module test_mod

use iso_fortran_env, only : RP => REAL16
!use iso_fortran_env, only : RP => REAL32
!use iso_fortran_env, only : RP => REAL64
!use iso_fortran_env, only : RP => REAL128

implicit none

contains

function eye(n) result(x)
!--------------------------------------------------------------------------------------------------!
! EYE returns an order n identity matrix.
!--------------------------------------------------------------------------------------------------!
implicit none

! Inputs
integer, intent(in) :: n
! Outputs
real(RP) :: x(max(n, 0), max(n, 0))
! Local variables
integer :: i

if (size(x, 1) * size(x, 2) > 0) then
    x = 0.0_RP
    do i = 1, int(min(size(x, 1), size(x, 2)), kind(i))
        x(i, i) = 1.0_RP
    end do
end if
end function eye

function isorth(A, tol) result(is_orth)
!--------------------------------------------------------------------------------------------------!
! This function tests whether the matrix A has orthonormal columns up to the tolerance TOL.
!--------------------------------------------------------------------------------------------------!
implicit none

! Inputs
real(RP), intent(in) :: A(:, :)
real(RP), intent(in), optional :: tol
! Outputs
logical :: is_orth
! Local variables
integer :: n
real(RP) :: err(size(A, 2), size(A, 2))

n = int(size(A, 2), kind(n))
err = abs(matmul(transpose(A), A) - eye(n))
is_orth = all(abs(matmul(transpose(A), A) - eye(n)) <= max(tol, tol * maxval(abs(A))))

write (*, *) 'A = ', A
write (*, *) 'A^T*A = ', matmul(transpose(A), A)
write (*, *) 'I = ', eye(n)
write (*, *) '|A^T*A - I| = ', err
write (*, *) 'max(|A^T*A - I|) = ', maxval(err)
write (*, *) 'tol = ', tol
write (*, *) 'max(tol, tol * maxval(abs(A))) = ', max(tol, tol * maxval(abs(A)))
write (*, *) '|A^T*A - I| <= max(tol, tol * maxval(abs(A))) = ', err <= max(tol, tol * maxval(abs(A)))
write (*, *) 'all(|A^T*A - I| <= max(tol, tol * maxval(abs(A)))) = ', all(err <= max(tol, tol * maxval(abs(A))))
write (*, *) '|A^T*A - I| <= tol = ', abs(matmul(transpose(A), A) - eye(n)) <= tol
write (*, *) 'all(|A^T*A - I| <= tol) = ', all(abs(matmul(transpose(A), A) - eye(n)) <= tol)
write (*, *) 'is_orth = ', is_orth
end function isorth

end module test_mod


program test
use test_mod, only : RP, isorth
implicit none
logical :: is_orth

real(RP) :: A(2, 2) = reshape([-0.7896_RP, 0.6143_RP, -0.6143_RP, -0.7896_RP], [2, 2])
real(RP) :: tol = 0.99_RP

is_orth = isorth(A, tol)

if (is_orth) then
    write (*, *) 'RIGHT! The columns of A are orthonormal up to the tolerance ', tol
else
    write (*, *) 'WRONG! The columns of A are not orthonormal up to the tolerance ', tol
    error stop 1
end if

end program test

Experiment:

$ uname -a && nagfor test.f90  && ./a.out
Linux 6.5.0-21-generic #21~22.04.1-Ubuntu SMP PREEMPT_DYNAMIC Fri Feb  9 13:32:52 UTC 2 x86_64 x86_64 x86_64 GNU/Linux
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7143
[NAG Fortran Compiler normal termination]
  A =  -0.7896  0.6143 -0.6143 -0.7896
 A^T*A =    1.001  0.0000  0.0000   1.001
 I =    1.000  0.0000  0.0000   1.000
 |A^T*A - I| =   0.0000  0.0000  0.0000  0.0000
 max(|A^T*A - I|) =   0.0000
 tol =   0.9902
 max(tol, tol * maxval(abs(A))) =   0.9902
 |A^T*A - I| <= max(tol, tol * maxval(abs(A))) =  T T T T
 all(|A^T*A - I| <= max(tol, tol * maxval(abs(A)))) =  T
 |A^T*A - I| <= tol =  T T T T
 all(|A^T*A - I| <= tol) =  T
 is_orth =  F
 WRONG! The columns of A are not orthonormal up to the tolerance   0.9902
ERROR STOP: 1

The bug occurs also on a Macbook with M3 chip and the latest system. The version of the compiler is the same.

A second bug, which has been reported to NAG confirmed by NAG.

Code (also available at test_compiler/test_mult.f90 at master · zequipe/test_compiler · GitHub):

! test_mult.f90
module test_mod

use iso_fortran_env, only : RP => REAL16
!use iso_fortran_env, only : RP => REAL32
!use iso_fortran_env, only : RP => REAL64
!use iso_fortran_env, only : RP => REAL128
implicit none

contains

function test(a, b, c) result(d)
real(RP), intent(in) :: a
real(RP), intent(in) :: b
real(RP), intent(in) :: c(2)
real(RP) :: d(2)

d = a * b * c
!d = a * (b * c)  ! Fine
!d = c * b * a  ! Fine

end function test

end module test_mod


program test_mult
use test_mod, only : RP, test
implicit none

real(RP) :: a = 0.99_RP
real(RP) :: b = 0.99_RP
real(RP) :: c(2) = [1.0_RP, 1.0_RP]

write (*, *) test(a, b, c)

if (all(abs(test(a, b, c)) <= 0)) then
    write (*, *) "WRONG! Product is zero"
    error stop 1
else
    write (*, *) "RIGHT! Product is not zero"
end if

end program test_mult

Test:

$ uname -a && nagfor -O1 test_mult.f90  && ./a.out
Linux 6.5.0-21-generic #21~22.04.1-Ubuntu SMP PREEMPT_DYNAMIC Fri Feb  9 13:32:52 UTC 2 x86_64 x86_64 x86_64 GNU/Linux
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7143
[NAG Fortran Compiler normal termination]
  0.0000  0.0000
 WRONG! Product is zero
ERROR STOP: 1

The bug occurs also on a Macbook with M3 chip and the latest system. The version of the compiler is the same.

A third bug, which has been reported to NAG confirmed by NAG.

Code (also available at test_compiler/test_abs.f90 at master · zequipe/test_compiler · GitHub):


! test_abs.f90
program test

use, intrinsic :: iso_fortran_env, only : RP => real16
use, intrinsic :: ieee_arithmetic, only : ieee_value, ieee_quiet_nan, ieee_is_nan

implicit none

real(RP) :: NAN_RP, A(2, 2), B(2, 2), E1(2, 2), E2(2, 2)

NAN_RP = ieee_value(0.0_RP, ieee_quiet_nan)

A = reshape([-0.0_RP, 0.0_RP, 0.0_RP, 0.0_RP], [2, 2])
B = reshape([NAN_RP, NAN_RP, NAN_RP, NAN_RP], [2, 2])
E1 = abs(matmul(B, A) - A)
E2 = abs(matmul(B, A) - B)

write (*, *) matmul(B, A)
write (*, *) abs(matmul(B, A))
write (*, *) matmul(B, A) - A
write (*, *) matmul(B, A) - B
write (*, *) abs(matmul(B, A) - A)
write (*, *) abs(matmul(B, A) - B)
write (*, *) ieee_is_nan(abs(matmul(B, A) - A))
write (*, *) ieee_is_nan(abs(matmul(B, A) - B))
write (*, *) E1
write (*, *) E2
write (*, *) E1 <= 0
write (*, *) E2 <= 0

if (.not. all(ieee_is_nan(E1)) .or. .not. all(ieee_is_nan(E2))) then
    write (*, *) 'Test failed'
    error stop 1
else
    write (*, *) 'Test passed'
end if

end program test

Test:

$ uname -a && nagfor -ieee=full test_abs.f90  && ./a.out
Linux 6.5.0-21-generic #21~22.04.1-Ubuntu SMP PREEMPT_DYNAMIC Fri Feb  9 13:32:52 UTC 2 x86_64 x86_64 x86_64 GNU/Linux
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7143
[NAG Fortran Compiler normal termination]
 NaN NaN NaN NaN
 NaN NaN NaN NaN
 NaN NaN NaN NaN
 NaN NaN NaN NaN
  0.0000  0.0000  0.0000  0.0000
  0.0000  0.0000  0.0000  0.0000
 T T T T
 T T T T
  0.0000  0.0000  0.0000  0.0000
  0.0000  0.0000  0.0000  0.0000
 T T T T
 T T T T
 Test failed
ERROR STOP: 1
Warning: Floating invalid operation occurred

The bug occurs also on a Macbook with M3 chip and the latest system. The version of the compiler is the same.

A fourth bug, which has been submitted to NAG.

Code (also available at test_compiler/test_mult_nan.f90 at master · zequipe/test_compiler · GitHub):

! test_mult_nan.f90

program test_mult_nan

use, intrinsic :: iso_fortran_env, only : RP => real16
use, intrinsic :: ieee_arithmetic, only : ieee_is_nan

implicit none

real(RP) :: A(2)

A = 1.0_RP
A = -1.0_RP * A

if (any(ieee_is_nan(A)) .or. any(abs(A + 1.0_RP) > 10.0_RP * epsilon(1.0_RP))) then
    write (*, *) 'A = ', A
    write (*, *) 'A is wrong!'
    error stop 1
end if

end program test_mult_nan

Experiment on Ubuntu 22.04:

$ uname -a && nagfor -ieee=full test_mult_nan.f90 && ./a.out
Linux 6.5.0-21-generic #21~22.04.1-Ubuntu SMP PREEMPT_DYNAMIC Fri Feb  9 13:32:52 UTC 2 x86_64 x86_64 x86_64 GNU/Linux
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7143
[NAG Fortran Compiler normal termination]
 A is wrong!
 A =  NaN NaN
ERROR STOP: 1

Experiment on macOS (M3 chip):

 % uname -a && nagfor test_mult_nan.f90&& ./a.out
Darwin 23.3.0 Darwin Kernel Version 23.3.0: Wed Dec 20 21:30:59 PST 2023; root:xnu-10002.81.5~7/RELEASE_ARM64_T6030 arm64
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7144
[NAG Fortran Compiler normal termination]
 A =   0.0000  0.0000
 A is wrong!
ERROR STOP: 1

Update (20240307):

  1. nagfor 7.1 Build 7149 released on March 5, 2024, fixed all the above four bugs, but introduced an ICE when compiling PRIMA. The ICE has nothing to do with half-precision real, because it occurs even if PRIMA is configured to use single or double precision.

    Code:

uname -a && git clone https://github.com/libprima/prima.git && cd prima && git checkout ec42cb0 && cd fortran/examples/lincoa && make ntest
Linux 6.5.0-21-generic #21~22.04.1-Ubuntu SMP PREEMPT_DYNAMIC Fri Feb  9 13:32:52 UTC 2 x86_64 x86_64 x86_64 GNU/Linux
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o consts.o ../../common/consts.F90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o infos.o ../../common/infos.f90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o debug.o ../../common/debug.F90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o huge.o ../../common/huge.F90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o inf.o ../../common/inf.F90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o infnan.o ../../common/infnan.F90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o memory.o ../../common/memory.F90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o string.o ../../common/string.f90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
[NAG Fortran Compiler normal termination]
nagfor -C -f2018   -fpp -nan -ieee=full   -O -g -c -o linalg.o ../../common/linalg.f90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7149
Panic: ../../common/linalg.f90, line 2704: Not a Uindex
Internal Error -- please report this bug
Abort
make: *** [linalg.o] Error 3
  1. nagfor 7.2 Build 7200 released on 6 March, 2024, included neither the ICE nor the fixes for the above-mentioned four bugs.
1 Like

Update (20240311): All the above bugs have been fixed by nagfor 7.2 Build 7201.

4 Likes