Function to detect NaN values

I wanted to write a replica of the Matlab function isnan (for those who don’t know it, here is a reference) and I came out with the following function.

module m
    implicit none
    
    contains
    !=====================================================================!
    elemental function isnan(x) result(tf)
    ! Purpose: this replicates the matlab function isnan
    implicit none
    real(8), intent(in) :: x
    logical :: tf
    
    tf = (x/=x)
    
    end function isnan
    !=====================================================================!
end module m
    
    
program test_isnan
    use m, only: isnan
    implicit none
    integer :: i,j
    real(8), allocatable :: x_vec(:),x_mat(:,:)
    logical, allocatable :: res(:),res_mat(:,:)
    !--------------------------------------------------------!
    
    allocate(x_mat(2,3))
    x_vec = [1.0d0, 0.0d0/0.0d0, 3.4d0]
    x_mat(1,:) = x_vec
    x_mat(2,:) = x_vec
    res = isnan(x_vec)
    res_mat = isnan(x_mat)
    
    write(*,*) "x_vec = "
    do i=1,size(x_vec)
        write(*,'(F5.3)') x_vec(i) 
    enddo
    
    write(*,*) "isnan(x_vec) = "
    do i=1,size(x_vec)
        write(*,'(L)') res(i) 
    enddo
    
    write(*,*) "isnan(x_mat) = "
    do i=1,size(x_mat,1)
        write(*,'(3L)') res_mat(i,:) 
    enddo
    
    
    pause 
    
end program test_isnan

I’d like to make sure if this is a good way of doing it or there are “better” alternatives.

Depending on your needs you can rely on the ieee_arithmetic module ieee_arithmetic in Fortran Wiki which already has a function for that, or you could have a read to this thread: Challenge: Testing Inf and NaN with `gfortran-13 -Ofast` for some ideas

2 Likes

From @zaikunzhang there is

1 Like

Here is what I use. I normally set WP to REAL64 but you can adjust it to be REAL32 etc if needed.

  Elemental Function isNaN(num)

    USE ieee_arithmetic, ONLY: ieee_is_nan

    Real(WP), Intent(IN) :: num
    Logical              :: isNan

    isNAN = ieee_is_nan(num)

  End Function isNaN

  Elemental Function isInfinite(num)

    USE ieee_arithmetic, ONLY: ieee_is_finite

    Real(WP), Intent(IN) :: num
    Logical              :: isInfinite

    isInfinite = (ieee_is_finite(num) .EQV. .FALSE.)

  End Function isInfinite

  Elemental Function isNanInf(num)

     Real(WP), Intent(IN) :: num

     Logical              :: isNanInf

     isNanInf = (isNan(num) .OR. isInfinite(num))

  End Function isNaNInf
1 Like

I think the above should be written more concisely as

isInfinite = .not. ieee_is_finite(num)

1 Like

In this case probably yes. However, I got in the habit of using .EQV. because I find that using .NOT. can sometimes be confusing (at least to me) when you have a complex logical expression that you are unsure if the correct result is .TRUE. or .FALSE. Obviously not this case, but sometimes habits die hard.

1 Like

I do not think x is necessarily infinity when ieee_is_finite(x) is false. x may be NaN.

Note that ieee_is_xyz does not work well when you compile your code with aggressive optimization flags like -Ofast, which motivates equipez/infnan.

Whether you should apply such optimization flags at all, it is a different question. I would not, but you cannot always control what the users of your code do.

1 Like

I normally only use isNAN etc when I’m debugging anyway (-O0 -g) so I’ve not found that to be an issue. What is an issue is how much the ieee_is_xxx functions can slow down a code so in my experience they are not something you use to just trap NaNs in general. Probably better to use the compiler options first to abort on NaN and use isNAN to narrow down what part of the code is triggering the NaN

1 Like