Exceptions proposal

As many of you know, some form of Exceptions support had been proposed for F2023, but discussions couldn’t establish a direction and it was dropped.

I was unaware that there were earlier proposals from before my time on the committee. Van Snyder @vsnyder posted 23-106.pdf (j3-fortran.org) with an updated version of the older proposal, and I found a lot in it I liked. I’d love to have people read this and offer their thoughts.

1 Like

I’m pretty sure I like it, other than a couple of minor comments.

I’m not sure about the ENABLE idea, specifically what he means by

and in contained blocks or subprograms, unless explicitly disabled.

For example

program
  use my_exception, only: foo
  call sub1
contains
  subroutine sub1() enable(foo)
    call sub2
  handle foo
    print *, "I caught it"
  end subroutine

  subroutine sub2() enable(-foo)
    call sub3
  end subroutine

  subroutine sub3()
    raise foo
  end subroutine
end program

Subroutine sub2 explicitly doesn’t detect exception foo, but isn’t a contained block or subprogram of sub1, so does sub1 detect the exception raised by sub3? It’s possible his description of propagating actually does cover this, but it wasn’t obvious.

Also, when handling an exception, an exception-data-variable has its value assigned

as if by execution of an assignment statement

This opens up defined assignment, which I’m not sure is a good idea. A defined assignment might be available at the raise statement, but not at the handle statement, so is it defined by intrinsic or defined assignment? At least for a first implementation It might be better to say

as if by intrinsic assignment

Other than that it definitely looks workable to me.

Van Snyder and others did already discuss the topic here: Exceptions and Exception Handling · Issue #172 · j3-fortran/fortran_proposals · GitHub

Personally, I do like the focus on the CHANGE TEAM construct as well as on the BLOCK construct in this proposal very much.

My major concern is currently with the END TEAM statement, if not all images may reach this because of some failure in code or hardware, and if the coarray runtime still can’t detect this (reliably). This is very much related to FAILED IMAGES and was the reason for my proposal here: Extending the FAIL IMAGE statement to allow to fail remote images · Issue #259 · j3-fortran/fortran_proposals · GitHub

Meanwhile, I am relatively sure that exception handling won’t work in many cases, as we can already see this with DPC++ for device codes (see below). (But am surely not against exception handling in Fortran for host codes).

This GitHub repository is still under construction and I could be completely wrong with any of the assumptions and conclusions there, but fear I am not: GitHub - MichaelSiehl/Spatial_Fortran_1

Error handling on devices (and host) is initially described for DPC++: Error Handling | SpringerLink .

See this quote from page 146 there:

“SYCL explicitly disallows C++ exception handling mechanisms (such
as throw) within device code, because there are performance costs for
some types of device that we usually don’t want to pay. If we detect that
something has gone wrong within our device code, we should signal the
error using existing non-exception-based techniques. ”

That is why I still do believe in a more advanced FAILED IMAGES feature to give some control to the programmer to successfully leave a coarray team in the case of a failure that the programmer can detect but the coarray runtime can’t detect.

Regards

Another option would be to have look at how Rust implements error handling. I am not competent in Rust enough, but as far as I know, it is one example of a thoughtfully designed modern language that does not need exceptions to handle errors.

As far as the proposal goes, at the beginning I really disliked that “handle” is not a block, but the more I look at it, the more I like it. It could really motivate the programmer to split the program into smaller units. (just as I hated that variable declarations cannot be done anywhere in code like C/C++, but now I actually think it is a feature, not a bug).

Dominik

1 Like

I have a few questions:

  • What are the performance implications of this proposal?
  • Why are many C++ applications turning off exceptions for performance (in gaming industry for example)?
  • The C++ committee does not seem to be super happy with their traditional exceptions, and are proposing a different mechanism: http://www.open-std.org/jtc1/sc22/wg21/docs/papers/2018/p0709r0.pdf; Wouldn’t it be a mistake to do what C++ found is not such a great idea?

The paper says “block-structured exception handling does not inevitably impose a significant execution-time penalty if an exception does not occur.” The C++ paper above talks at depth of the actual costs of “zero overhead” exceptions. Is this Fortran proposal different in terms of performance?

4 Likes

I’ve looked at it, and Rust implements error handling via return types. It’s type safe and unignorable, meaning it wouldn’t be backwards compatible with existing code. You couldn’t add error handling to some low level library, maintain the existing interface, and be able to catch it levels up the call stack that way. Also, I don’t believe Rust’s mechanism is any more “performant” than C++. I don’t what they’ve claimed about it, but generally when Rust says “zero overhead”, they mean you couldn’t implement it in a more optimized way yourself.

I’ll admit I haven’t fully understood the semantics of C++ exception handling vs how this proposal would be different, but my hope is that there are some semantic differences that would allow this to be more performant. I’m hopeful someone more experienced in such things can investigate that and let us know.

1 Like

I overall like this proposal.

As I understand it, it proposes that the detection of built-in exceptions is always enabled. I didn’t see a way to disable the detection of some or all exceptions.

I think it would be desirable to be able to disable exceptions programmatically, by unit scope or altogether.

My understanding of exception handling may be naive, but I thought that no matter how “zero-cost” this exception handling is, there must be some non-zero cost because it’s impossible to create information without spending energy.

TL;DR: Start small with exception handling in Fortran 202Y will be my recommendation.

For whatever it’s worth, I do not at all like the working approach in this paper by @vsnyder :

  1. It immediately jumps into a “solution mode” with very little to poor treatment of the desired use cases,
  2. Besides, the solution approach laid down in the paper appears rather outdated. A lot of “water” has flown since the paper was first put together and slapping a recent date on it does not make it any current or relevant for future.
  3. A lot of effort has gone into the standard with IEEE floating-point exceptions that at least for now, floating-point exceptions need not be covered in the above-mentioned use cases, at least during first revision of exception handling in the standard,
  4. That is, any initial treatment of exception handling in Fortran 202Y (hopefully this is the revision that will introduce something; if not, then Fortran 203X) should study all the use cases closely and consider working toward a few simpler cases only based on guidance from compiler implementations re: run-time cost and also the possibilities of prototyping such as with LFortran based on feedback from @certik and team.

In terms of use cases, my suggestion(s)

  1. for the first case is when an ERROR STOP statement instruction takes place in a library method that initiates “error termination” by a Fortran processor. Here the use case will be for the caller to be able to supply a “handler” method, perhaps with certain defined interfaces (a la defined IO), and which then gets executed with some defined semantics during the error termination. The caller can then complete needed actions in this handler. A loose analogy might be the FINAL procedure with finalizable types.
  2. a companion to case 1 i.e., when a Fortran subprogram is invoked by a processor other than a Fortran main program, then to extend the handler scheme toward some procedure interoperable with a C companion processor.

As far as I am concerned, if Fortran 202Y can cover just these 2 use cases, it will more than satisfy the 80-20 rule (Pareto principle) with the needs we have noticed in industry with Fortran codes (primarily libraries aka DLLs).

If I understand it correctly, exception handling is not just turned off but rather not even supported in device kernel (coroutine) codes, because the cost alone would make devices useless.

Exception handling can merely be on the host, synchronously for errors in the host program and asynchronously for device kernels, but no exception handling on the device itself.

Since (future) Fortran compilers may be enabled to compile for devices, such should be considered with an exceptions proposal, I think.

2 Likes

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

| FortranFan
February 10 |

  • | - |

TL;DR: Start small with exception handling in Fortran 202Y will be my recommendation.

For whatever it’s worth, I do not at all like the working approach with this paper by @vsnyder :

  1. It immediately jumps into a “solution mode” with very little to poor treatment of the desired use cases,

The history of the world, or of Fortran, does not start anew with each new revision of the standard.

The history of exception handling is so long that we probably don’t need remedial tutoring about its fundamental principles. John Reid described block-structured exception handling for Fortran 2003, using integers instead of enumerators to identify exceptions, at the 1998 meeting in Trollhättan. Unfortunately, this was an oral presentation, and there was no meeting paper. Discussion of it had certainly preceded his proposal (e.g., see WG5 papers N1052 and N1257).

The lists of “use cases” are the lists of enumerators in Sections 5.1 and 5.2 in 23-106, each of which identifies an error condition specified by the standard. If one wants to understand the details of error conditions, one can read 23-007. Further explication in 23-106 would be needlessly duplicative.

  1. Besides, the solution approach laid down in the paper appears rather outdated. A lot of “water” has flown since the paper was first put together and slapping a recent date on it does not make it any current or relevant for future.

An explanation of a newer alternative methodology, along with a detailed description how to integrate it compatibly into Fortran, would be interesting to see, in a different paper.

We already have the older methodology of status variables, but they can’t catch things like failing to elaborate the specification part of a procedure or BLOCK construct because some automatic variables are too big.

  1. A lot of effort has gone into the standard with IEEE floating-point exceptions that at least for now, floating-point exceptions need not be covered in the above-mentioned use cases, at least during first revision of exception handling in the standard,

There are many use cases listed in Sections 5.1 and 5.2 in 23-106, in addition to IEEE floating point exceptions. Just last week, I had a code that failed at the SUBROUTINE statement of an internal subroutine. It took significant time to work out that an error in the specification of an array had resulted in failure to materialize all the automatic variables. Printing an exception would have been more informative than SEG FAULT. In many applications, being able to catch this particular failure would allow one to use a slower but less memory-intensive algorithm, instead of printing a mysterious SEG FAULT message.

  1. That is, any initial treatment of exception handling in Fortran 202Y (hopefully this is the revision that will introduce something; if not, then Fortran 203X) should study all the use cases closely and consider working toward a few simpler cases only based on guidance from compiler implementations re: run-time cost and also the possibilities of prototyping such as with LFortran based on feedback from @certik and team.

Many other languages have had block structured exception handling, some for several decades. As Kenneth Louden noted in Programming Languages: Principles and Practice, design questions were largely resolved about thirty years ago. The experience with Ada compilers, and perhaps compilers for other languages, is that block-structured exception handling can be implemented with very small execution-time overhead unless and until an exception occurs. Indeed, the GNU Ada Translator developers claim that with their processor, there is zero execution-time overhead unless and until an exception occurs.

Surely Fortran processor developers are able to learn from the developers of processors for other languages. I can provide contact information for members of WG9.

In terms of use cases, my suggestion(s)

  1. for the first case is when an ERROR STOP statement instruction takes place in a library method i.e., when “error termination” is initiated by a Fortran processor. Here the use case will be for the caller to be able to supply a “handler” method, perhaps with certain defined interfaces (a la defined IO), and which then gets executed with some defined semantics during error termination. The caller can then complete needed actions in this handler. A loose analogy might be the FINAL procedure with finalizable types.

Starting small and promising to finish the job in ten or twenty years was the reason that people fled from Fortran to C and C++ and Python and … starting about 1988. PLEASE, NO MORE HALF MEASURES IN FORTRAN! And no more kludges. If we had done templates before 2003, we wouldn’t have provided for derived types with kind type parameters, which invite one to write almost-perfectly reasonable code that cannot be compiled. (Simply declare an object using a kind type parameter for which there is a missing type-bound procedure with the required spectrum of kinds of its dummy arguments. Richard Maine warned of this before 2003). If we had provided for decisions embedded in expressions, with the ability to calculate whether an actual argument is present, we wouldn’t have done the kludge of a disassociated pointer or deallocated allocatable variable corresponding to an optional nonpointer nonallocatable dummy argument being considered to be absent. (I proposed embedded decisions before 1990, but MERGE existed and I didn’t at the time appreciate the difference between eager and lazy function argument evaluation so I let it go.)

But if you insist on not doing block-structured exception handling now, print material about alternate returns in full-size type, because that’s the only exception handler that Fortran currently has, other than ERR= and END= in input/output statements.

  1. a companion to case 1 i.e., when a Fortran subprogram is invoked by a processor other than a Fortran main program, then to extend the handler scheme toward some procedure interoperable with a C companion processor.

As far as I am concerned, if Fortran 202Y can cover just these 2 use cases, it will more than satisfy the 80-20 rule (Pareto principle) with the needs we have noticed in industry with Fortran codes (primarily libraries aka DLLs).

A handler as described in 23-106 can invoke a procedure defined by the companion processor. There is no need to be able to specify that a handler is provided by a companion processor. Whether it is possible to raise an exception that one expects to be handled by a main program or calling procedure defined by a companion processor should be processor dependent, not mandated by the standard.

Ordinarily I would be among the first to comment in support of the proposition to not adopt half measures or kludges in Fortran, even as I don’t have the means to secure voting rights on a standard committee nor any institutional backing or credentials beyond that of a mere Fortran enthusiast.

However I do take a strong exception (!!) with the case of exception handling given the learnings over the last 6-10 years with other languages, especially with those that went all in with block structured exception handling.

Not doing anything at all, I believe, will be better than trying to imitate Ada or C++ or Rust, etc.!!

Exception handling is not like enumerations, a simpler compile time organization toward related set of constants, where Fortran could have gone with a lot of ideas from 2018 Swift but did not and instead went with 1980 Pascal and some Ada to the detriment of modern practitioners.

Getting exception handling as poorly designed given increasing importance of functional and concurrent and parallel programming paradigms can have considerably adverse runtime consequences for Fortran.

As things stand, not doing anything initially in the context of SUBROUTINE subprograms is not a big deal, I feel.

The place to start will be FUNCTION subprograms and to focus on the ability to consume functions in expressions without the burden of significantly “defensive” programming for those cases that indeed would be infrequent exceptions! Currently ERROR STOP is the brute force mechanism to help with these situations. . Starting small and helping out here will be good I think.

Separately I have reviewed closely a fair amount of earlier viewpoints such as the papers in non-J3 sources by Reid e.g., here. Current Fortran standard with its IEEE floating point exception handling facilities supersedes much of the earlier arguments and designs so much so that the focus can be on other limited aspects such as around ERROR STOP.

Hence my suggestion to start anew with a smaller scope and my points above.

In C++ floating point exceptions are not related to and not catch-able by the try/catch mechanism without the user supplying some specific signal handler.
Because the exception mechanism does catch the errors it can be hard to locate where they actually occur when debugging - for that reason enclosing them in #ifndef DEBUG is one technique for handling effectively disabling them.
Do any of the proposals have a mechanism for disabling them or would we be compelled to use the cpp?

The next time someone pokes fun at the standards committee for not having added exceptions to the language already, I’ll just point them at this thread.

I really miss the thoughtful design of VAX/VMS where each procedure invocation had a reserved spot in the stack frame for the address of an exception handler, and the OS would, upon a processor or OS detected error, or one initiated by a call to LIB$SIGNAL, would work its way up the call stack, calling each handler (if any) in turn. A handler could choose to handle the exception, resignal it to the next level, or exit the program. This mechanism was available to all languages and had no overhead for code that didn’t use it. Sadly, such forethought has been largely lacking in later platforms.

I regret that I am unfamiliar with some of these newer languages. I did know Ada in the 1980s (I was on the VAX Ada project) and I do like having the handling code attached to the block it belongs to (I think C++ try/except is the same.)

As I see it, there are two main use cases for exception handling. One is to gracefully detect and report/log the exception and exit the current operation (or program). The other is to attempt some sort of recovery. These aren’t necessarily conflicting goals. The model we have for IEEE_EXCEPTIONS works for both of these, but requires the user to explicitly check for conditions, and the processor needs to know if it must be pessimistic about possible exceptions or if it can just try to run with the blade guards off.

I wish I knew how exceptions in C++ or other languages were implemented “under the hood” - that would give me a better feel for what is possible in a platform-neutral manner.

For me, the “minimum viable product” is one where:

  • Handling code is attached to procedures or blocks
  • The handling code can get enough details of the exception to be able to make intelligent decisions
  • The handling code can choose to ignore the exception (continuing if possible), pass the buck up the nesting chain, report/log the condition and somehow allow the program to continue (or not as the case may be)
  • Little or no overhead if a procedure/block doesn’t ask to handle exceptions

There are other “nice to have” things, but I’d like to think the above would satisfy a large part of the user base.

2 Likes

There is no indication knowing any details of C++ “under the hood” is all that important.

What is more important is, as urged by @certik upthread, to avoid the mistakes of C++ (recognized broadly) and other block structured exception handling attempts in other languages that are not as well known or understood as much due to their far lesser usage and thus attention on them.

Re: C++, another thing to know is it’s very much work in progress, the abstract at this link is a quick read and it can be noted the issues laid down are still being worked on:

Divergent error handling has fractured the C++ community into incompatible dialects, because of long-standing unresolved problems in C++ exception handling. This paper enumerates four interrelated problems in C++ error handling. Although these could be four papers, I believe it is important to consider them together.

§4.1: “C++” projects commonly ban exceptions, largely because today’s dynamic exception types violate zero-overhead and determinism, which means those are not really C++ projects but use an incompatible dialect. —

We must at minimum enable all C++ projects to enable exception handling and to use the standard library. This paper proposes extending C++’s exception handling to let functions declare that they throw a statically specified type by value, which is zero-overhead and fully deterministic. This doubles down on C++’s core strength of effi­cient value semantics, as we did with move semantics as a C++11 marquee feature.

§4.2: Contract violations are not recoverable run-time errors and so should not be reported as such (as either exceptions or error codes). — We must express preconditions, but using a tool other than exceptions. This pa­per supports the change, already in progress, to migrate the standard library away from throwing exceptions for precondition violations, and eventually to contracts.

§4.3: Heap exhaustion (OOM) is not like other recoverable run-time errors and should be treated separately.

— We must be able to write OOM-hardened code, but we cannot do it with all failed memory requests throwing bad_alloc. This paper supports proposals like [P0132R0], already in progress, to extend the new(nothrow) ap­proach to STL with “try” functions or similar (e.g., try_reserve).

§4.5: Some users don’t use exceptions because exceptional control flow is invisible. — We must have auto­matic propagation, but also the ability to make it visible. This paper proposes allowing try-expressions to make exceptional paths concisely explicit in calling code, without losing any of the benefits of automatic propagation.

As someone who, in a past life, would have been involved in implementing it, I say it IS important. We can’t have a discussion about performance impact without at least some developers chiming in on how they would implement a proposal. If we care about performance, and we do, it matters.

3 Likes

I spent a few minutes wracking my brain for motivations for exception handling in Fortran, since I feel there has to be clear motivating examples beyond “other languages do it”, which may help in guiding the discussion. In some other languages (used to e.g. maintain 24/7 accessible online databases) you need exception handling just to ensure things don’t break for vital users/customers.

Along those veins, the examples I can think of useful for Fortran (nominally HPC):

  • If an image (or team) fails in their work, say due to one node out of twenty failing, one can move the work to another team. As I understand it, this is somewhat handled by current F18, but the documentation I found suggests images may not always be correct/up-to-date on if other images have failed, due to synchronization issues.
    – If an image raises an exception, but the exception is being handled, there is ambiguity in whether or not it should be considered a failed image. One could go the route of no, and then one can in-principle use fail_image() inside the exception handling if necessary to still indicate to other images this image is failed, and thus elevate fail_image() from a purely testing/debugging statement to part of exception handling.
  • Graceful exits for exceptions, allowing you to save intermediate work if possible on long calculations. Though if the exception was say the hard disk running out of memory, this will again cause a failure.
    – Thus, do we allow exception handling within exception handling? I don’t see why not, although it could lead to weird outcomes…
  • Printing out possibly relevant debugging information.
  • As pointed out above by FortranFan, if an external program calls a Fortran library and an exception occurs, it may be useful to be able to specify alternative behavior for the sake of the external program.
  • There are, I’m sure, a few industrial Fortran programs that need to be running 24/7 like the above database example, and exception handling may give some power to that end.

In terms of performance, I know little about it, but it could be useful to make sure the exception handling structures are “easy to ignore” for compilers, i.e. make it easy for a compiler to compile the code while ignoring the error handling statements, so that we can pass a flag that says “ignore exception handling”. This would make it easier to measure performance impact of error handling, if we can switch it off. Or as @simong mentioned, being able to turn it off would possibly make debugging easier if our debugging statements don’t seem to give us enough information.

1 Like

Ok well, it will be then useful if you can research it and post your learnings in an info paper and summarized in a tutorial presentation at a plenary. Past life can hopefully provide some view into how icc and icx do it, also gcc and perhaps LLVM.

For a concrete use case, let’s consider we’d like to provide a library function for calculating the arithmetic mean. I.e.

pure function mean(vals)
  real, intent(in) :: vals(:)
  real :: mean

  mean = sum(vals) / size(vals)
end function

The above is an absolutely sensible implementation, but alas there is a possible uncaught error. So what should be done. Current options are

pure function mean(vals)
  real, intent(in) :: vals(:)
  real :: mean

  associate(n => size(vals))
    if (n > 0) then
      mean = sum(vals) / n
    else
      mean = 0.0
    end if
  end associate
end function

which is again reasonable, but has two disadvantages. We have introduced some overhead for all situations, including non-exceptional ones, and made an explicit decision (which cannot be undone by users) for what should be done in the exceptional case. We could address the later by

pure subroutine mean(vals, res, stat)
  real, intent(in) :: vals(:)
  real, intent(out) :: res
  integer, optional, intent(out) :: stat

  associate(n => size(vals))
    if (n > 0) then
      res = sum(vals) / n
    else
      if (present(stat)) then
        stat = DIVIDE_BY_ZERO_ERROR
      else
        error stop "zero size array in mean"
      end if
    end if
  end associate
end subroutine

But this has the disadvantage that the procedure can no longer be used in expressions, and doesn’t address our performance penalty issue.

If exceptions are added to the language, one can just write the completely sensible first case. While some overhead may be incurred by such a feature, it is not as much as would be incurred by any of the other mechanisms of error handling currently available to us. For many use cases I’d suggest exceptions would actually be “negative overhead”, as it allows one to write simpler code with better performance than would otherwise be possible. Are there some pitfalls to avoid and details to iron out, sure, but to say that we shouldn’t pursue it because some other languages now regret their particular specification is throwing the baby out with the bathwater (IMO).

2 Likes

I don’t understand this argument. Please consider my comment upthread where I show a fully worked example using current Fortran standard and the IEEE facilities that have gone into the standard since Fortran 2003.

How is a library function mean any different in this context than the standard intrinsic norm2 function?

My point being any function, especially any that is doing a floating-point exception which is the overwhelming majority of computations using Fortran, can arrive at an “exception” scenario, the above example showing a divide-by-zero exception.

Fortran, unlike other languages, has put in a lot of effort with intrinsic IEEE facilities. All the teams I work with have exclusively been using IEEE computers for quite a while now and they expect to remain as such for a long-time into the future.

So it makes sense to me to first leverage the work that has already gone in toward IEEE exception handling. A lot of the early papers such as by John Reid appear to address doing something about floating-point exception handling, but that was before the IEEE facilities got introduced and thus a lot of early concerns have already been addressed in the standard.

Then consider that authoring library functions that raise exceptions is highly problematic. Please see this paper from 2022:
https://www.open-std.org/jtc1/sc22/wg21/docs/papers/2022/p2544r0.html

This paper is also relevant in terms of the concerns it raises in that the problems are present with languages other than C++ e.g., .NET, etc., almost any that adopts the couple of approaches with block structured exception handling. This is leading to a scenario where a big number of projects are deciding to not use or actively disable exceptions.

Thus the point I make about going "small and slow** here, and this is given the various informal feedback I have received.

As I wrote above, the first thing I get told is what can Fortran do about ERROR STOP. Can not Fortran first work out something simple and convenient for callers to provide some means to complete some steps as part of Fortran error termination?

The feedback I constantly get is for Fortran to solve this ERROR STOP handling problem with error termination first, preferably in Fortran 202Y. And only then to consider the broader aspect of fine-grained exception handling, later starting Fortran 203X.