Exceptions proposal

The example listed in the paper mentioned in the original post tries to intersperse IEEE exception handling in the standard (or earlier draft of it, perhaps from the time of Fortran 2003 work). As I mentioned, I will advise staying from any such solution proposals until after the use cases are fully understood and the simpler cases are addressed.

As far as I am concerned, the current standard offers most means needed to handle floating-point exceptions. A variant of the example posted in the above paper will be as follows:

module norm2_m

   use, intrinsic :: iso_fortran_env, only : RK => real_kinds

   use, intrinsic :: ieee_arithmetic, only : ieee_value, ieee_quiet_nan, ieee_positive_inf,         &
                                             ieee_is_nan

   use, intrinsic :: ieee_exceptions, only : ieee_invalid, ieee_all, ieee_get_flag, ieee_set_flag,  &
                                             ieee_get_halting_mode, ieee_set_halting_mode

   generic :: norm2 => norm2_k1_r1

contains

   impure function norm2_k1_r1( x ) result( L2norm ) !<-- impure only for illustration using PRINT statements

      ! Argument list
      real(RK(1)), intent(in) :: x(:)
      ! Function result
      real(RK(1)) :: L2norm

      ! Local variables
      intrinsic :: norm2
      logical, parameter :: IEEE_ALL_OFF(size(ieee_all)) = .false.
      logical :: CurrFlags(size(ieee_all))
      logical :: CurrModes(size(ieee_all))
      logical :: CalcFlags(size(ieee_all))
      integer :: i

      ! Get current IEEE flags and modes
      call ieee_get_flag(ieee_all, CurrFlags)
      call ieee_get_halting_mode(ieee_all, CurrModes)
      ! Clear flags, don't set halting
      call ieee_set_flag(ieee_all, IEEE_ALL_OFF)
      call ieee_set_halting_mode(ieee_all, IEEE_ALL_OFF)

      print *, "Using norm2_k1_r1:"
      ! Determine the L2 norm
      L2norm = norm2( x )

      ! Get updated IEEE flags
      call ieee_get_flag(ieee_all, CalcFlags)
      call ieee_set_flag(ieee_all, CurrFlags)
      call ieee_set_halting_mode(ieee_all, CurrModes)

      if ( all(.not. CalcFlags) ) return

      ! Handle the flags as desired
      if ( CalcFlags(1) ) then
         ! IEEE_INVALID case
         print *, "Handling IEEE_INVALID case" 
         if ( any ( ieee_is_nan(x) ) ) then
            L2norm = ieee_value( L2norm, ieee_quiet_nan )
         else
            L2norm = ieee_value( L2norm, ieee_positive_inf )
         end if
      else if ( CalcFlags(2) .or. CalcFlags(4) ) then
         ! IEEE_UNDERFLOW or IEEE_OVERFLOW case 
         block
            real(RK(1)) :: xmax
            xmax = maxval ( abs ( x ) )
            L2norm = xmax * norm2( x/xmax )
         end block
      else if ( CalcFlags(3) ) then !<-- Unexpected case
         error stop "Unexpected exception encountered."
      end if

      return

   end function norm2_k1_r1

end module norm2_m

   use, intrinsic :: ieee_arithmetic, only : ieee_value, ieee_is_finite
   use norm2_m, only : norm2

   real :: x(2), L2norm

   x = [ 3.0, 4.0 ]
   L2norm = norm2( x )
   print *, "norm2(x): ", L2norm

   ! Set array elements to values that can lead to inexact L2 norm
   x = huge(x)
   L2norm = norm2( x )
   print *, "Is L2norm finite? ", ieee_is_finite( L2norm ), "; expected is false"

end
  • Program response by a Fortran 2018 processor of this variant is
C:\temp>ifort /standard-semantics /free norm2.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.8.0 Build 20221119_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:norm2.exe
-subsystem:console
norm2.obj

C:\temp>norm2.exe
 Using norm2_k1_r1:
 norm2(x):  5.000000
 Using norm2_k1_r1:
 Handling IEEE_INVALID case
 Is L2norm finite?  F ; expected is false

C:\temp>

I request the readers to note a few aspects here

  1. Current standard already offers fine-grained control over IEEE floating-point exceptions. Now consider, say, Fortran 202Y: an overwhelming majority of computations using this standard revision can be expected to employ IEEE floating-point arithmetic. Thus one need not, from a practical consideration, place further effort at this stage on floating-point exception handling as part of Fortran 202Y, Now, arguably, one might view the standard IEEE facilities a bit old-fashioned and seek “wrapping” in more modern “classes” (types) for use in modern Fortran codes. But this can come later.
  2. So, with the example here, one can see the module and the subprogram therein as “library” code. And notice with this “library” code, nothing new with exception handling is introduced relative to current standard i.e., no added cost. That is a viewpoint I suggest - no added cost in library codes due to any facility introduced new.
  3. But then one gap is some unanticipated scenario where the example above calls ERROR STOP. So here the use case will be for the caller to supply the handler for it before the Fortran processor completes the error termination steps.
1 Like