j3-fortran / fortran_proposals

Proposals for the Fortran Standard Committee
178 stars 15 forks source link

Exceptions in Fortran #236

Open aradi opened 2 years ago

aradi commented 2 years ago

Based on the discussion on fortran-lang.discourse about the ErrorFx library, a mechanism for exception like error handling should be created.

ErrorFx demonstrates, that such a mechanism is possible with current Fortran already. But it needs a lot of boiler plate code, which in ErrorFx are currently substituted by Fypp-macros. I drafted a possible syntax for all the scenarios we can already handle in ErrorFx. I'd also provide equivalent Fortran code, but probably we can already start discussion, in case somebody sees some general flaws in the concept.

! All errors are extensions of a base type
type, extends(fatal_error) :: io_error
  character(:), allocatable :: name
  integer :: unit = - 1
end type io_error

type, extends(fatal_error) :: allocation_error
  integer :: allocation_size
end type allocation_error

subroutine subroutine_with_error(...) throws(io_error, allocation_error)
  ...
  throw io_error(name="somefile.dat")
 ...
end subroutine subroutine_with_error

function function_with_error(...) result(...) throws(io_error)
  ...
  throw io_error(unit=9)
  ...
end function function_with error

! Propagating error upwards
try call subroutine_with_error()

! Propagating error upwards in function call
i = try function_with_error()

! Catching if any error thrown and assign a default value in that case
i = try function_with_error() else -1

! The classical try-catch block
! errorvar is the name of the local variable representing the error which was caught
! If an error is not handled here, it will be automatically propagated upwards
try catch (errorvar)
  i = function_with_error
  ! or altenatively
  call subroutine_with_error()
catch (io_error)
  ! do something
  print *, "UNIT:", errorvar%unit
  ! We pass it upwards as a more generic error
  throw fatal_error :: errorvar
catch (some_other_error)
  ! do something else for this error
end try catch

! A call to a subroutine or a function with error outside of a try should trigger a compiler error
call subroutine_with_error()  ! should trigger compiler error
i = function_with_error()   ! should trigger compiler error as well
aradi commented 2 years ago

Actually, if we wanted to omit the central error type and take out inheritance from the game, we could just allow the user to declare arbitrary types (with some constraints, like no pointers in them) as "throwable" without having them to derive from a base class, e.g.

type, throwable :: io_error
  character(:), allocatable :: filename
  integer :: unit = -1
end type io_error

That would be probably even more "fortranic". Maybe then catch will need a catch all clause, as the errors were not hierarchical any more, so a catch(fatal_error) won't catch everything:

try catch (errorvarname)
...
catch all
  ! things to do, if the error type is irrelevant.
  ! As we don't know what the type is, no
  ! access to errorvarname is allowed here
end try catch
certik commented 2 years ago

@aradi thanks for opening up an issue for this to start a discussion.

So the single line try syntax is very good:

! Propagating error upwards
try call subroutine_with_error()

! Propagating error upwards in function call
i = try function_with_error()

! Catching if any error thrown and assign a default value in that case
i = try function_with_error() else -1

It greatly simplifies error handling, but it is just nicer syntax for what can be done already, as you have shown with your ErrorFx library. For reference, to make this proposal standalone, the proposal is that this code:

subroutine routine_propagating_error(..., error)
  ...
  type(fatal_error), allocatable, intent(out) :: error
  ...
  ! If error happend, we propagate it upwards, otherwise we continue
  try call routine_with_possible_error(...)
  print "(a)", "Apparently no error occured"
  ...
end subroutine routine_propagating_error

is equivalent to:

subroutine routine_propagating_error(..., error)
  ...
  type(fatal_error), allocatable, intent(out) :: error
  ...
  call routine_with_possible_error(..., error)
  ! If error happend, we propagate it upwards, otherwise we continue
  if (allocated(error)) return
  print "(a)", "Apparently no error occured"
  ...
end subroutine routine_propagating_error

There is no "magic" behind the scene.

Can you write what this code is equivalent to:

try catch (errorvar)
  i = function_with_error
  ! or altenatively
  call subroutine_with_error()
catch (io_error)
  ! do something
  print *, "UNIT:", errorvar%unit
  ! We pass it upwards as a more generic error
  throw fatal_error :: errorvar
catch (some_other_error)
  ! do something else for this error
end try catch

I think we have not discussed this part yet.

aradi commented 2 years ago

@certik To ease the communication and discussion, I've created the FException repository which contains the new syntax for all cases I've considered so far (throwing error, propagating error, catching error, error in functions) and also the equivalent Fortran 2008 code. (They can be compiled and executed).

I've slightly changed the syntax for the assignment to

try i = function_with_error(...)

to be more similar to the try call version (and because the try should relate to the entire expression, not just to the function call.

A try-catch construct of the form (see catch_exception_fxy.f90)

try catch
  call subroutine_throwing_error(ii)
  !call subroutine_throwing_error2(...)
catch (io_error as errorvar)
  print "(a)", "main: caught io_error"
  if (allocated(errorvar%message)) print "(2a)", "Message: ", errorvar%message
  if (allocated(errorvar%filename)) print "(2a)", "File name: ", errovar%filename
  print "(a,i0)", "Unit: ", errovar%unit
catch all
  print "(a)", "main: obtained some error, but I did not care to obtain its details"
end try

would be substituted with (see catch_exception.f90)

try_catch: block
  class(*), allocatable, target :: internal_errorvar

  try: block
    call subroutine_throwing_error(ii, internal_errorvar)
    if (allocated(internal_errorvar)) exit try
    ! call subroutine_throwing_error2(..., internal_errorvar)
    ! if (allocated(internal_errorvar)) exit try
    exit try_catch
  end block try

 select type (internal_errorvar)
  type is (io_error)
    catch_io_error: block
      type(io_error), pointer :: errorvar
      errorvar => internal_errorvar
      print "(a)", "main: caught io_error"
      if (allocated(errorvar%message)) print "(2a)", "Message: ", errorvar%message
      if (allocated(errorvar%filename)) print "(2a)", "File name: ", errorvar%filename
      print "(a,i0)", "Unit: ", errorvar%unit
      exit try_catch
    end block catch_io_error
  class default
    print "(a)", "main: obtained some error, but I did not care to obtain its details"
  end select
end block try_catch

Of course, apart of transforming the new syntax into the equivalent Fortran 2008 code, the compiler will need to check, whether all possible exceptions, which the code in the try block could throw, had been handled. If not, they must be either propagated upwards (provided the containing scopes throws(..) clause contains the unhandled exception types) or the compiler must stop with an appropriate error message.

certik commented 2 years ago

I see, nice. I didn't know you can exit from a "block".

What is nice about this approach to exception handling is that there are no extra features needed in the compiler "backend", no long jumps, no stack unwinding, no magic. All this is is just a nicer syntax, checked by the compiler's "frontend", but underneath using current Fortran features, so regarding questions like performance there is no additional overhead over what you would need to write by hand anyway.

@aradi, regarding try i = function_with_error(...), what about: try i = (function_with_error(...)**2 + 1)*another_function_with_error(...)? Would the try propagate in the whole expression to any function that returns an error? In which case the error can always be propagated as an extra argument (whether subroutine or a function). This would eliminate the need for theResult<T> type, which is not as easy to do in Fortran.

certik commented 2 years ago

Finally, exceptions have been discussed a lot in this repository. Here are other relevant threads: #6, #66, #172.

See this C++ paper about a try proposal for C++: http://www.open-std.org/jtc1/sc22/wg21/docs/papers/2018/p0709r0.pdf

See this thread in J3 about approaches to exceptions for Fortran:

In particular, a "status" variable:

Copying the relevant part here:


To make it clear what I am talking about, here is an example code in current Fortran:

https://gist.github.com/certik/bd8235d2e1d049b22fcd1016f4914430

Here is my original "try" proposal:

https://gist.github.com/certik/d950b7468228ff6f7d8bbc680a0943a7

and here is the new "status" proposal:

https://gist.github.com/certik/2293270ac39f2589ae702ed751f405f8


In particular, the "original try proposal" is very similar to your "try" above. It doesn't throw allocatable derived type, but just an integer, although I think it probably can be extended to other types. But it's the same idea. The "status proposal" adds a status attribute to the return error value, and then the compiler knows to handle it if it is hot handled explicitly. Just a variation on the above theme.

The main objection to the "status" proposal from the J3 thread above is that

There is no simple way of accommodating all of the various schemes that libraries have for reporting problems. For example, some of the Windows API routines return zero on failure and make you call GetLastError to get the "real" error., others return zero on success and an error code on failure. Any attempt to standardize how a "status" argument should behave is, I feel, doomed to failure.

I think that is true that whatever we propose does not directly map into every possible error handling mechanism that a library might use. I think the idea of the above proposal (and its variations) is that it allows a simple solid mechanism to handle errors in Fortran that people can use, but don't have to. If they choose to use it, it should work for almost any use case, but one must adapt the library a bit. Perhaps gradually.

aradi commented 2 years ago

@aradi, regarding try i = function_with_error(...), what about: try i = (function_with_error(...)**2 + 1)*another_function_with_error(...)? Would the try propagate in the whole expression to any function that returns an error? In which case the error can always be propagated as an extra argument (whether subroutine or a function). This would eliminate the need for theResult<T> type, which is not as easy to do in Fortran. Indeed, I've tried to play around with the analog to Result<T>, but that is a mess in current Fortran, as you have to create a wrapper type for every function result type. Although, that may get more straightforward, if templates appear in Fortran (202y?)...

I think, the try should apply to the entire rhs of the assignment (and even to the assignment itself, if we ever allow user defined assignments to throw exceptions...). I have no idea, how compilers deal wit the evaluation of complex expressions, but in current Fortran one would have to decompose the expression in its parts with maximally one error-throwing function call, then make the call, store the temporary result, make the check for the error, and then continue with the other parts of the expression. The one-liner

try res = function_throwing_error1(ierror)&
    & + function_throwing_error2(ierror)

has the Fortran equivalent

    try: block
      integer :: tmpres1, tmpres2
      tmpres1 = function_throwing_error1(ierror, internal_errorvar)
      if (allocated(internal_errorvar)) return
      tmpres2 = function_throwing_error2(ierror, internal_errorvar)
      if (allocated(internal_errorvar)) return
      res = tmpres1 + tmpres2
    end block try

(See also funcexpr_exception.f90 and funcexpr_exception_fxy.f90.)

The biggest problem I have with this variable extending approach, that we would be not allowed to use the exception mechanism in pure functions, while pure subroutines would be no problem. Of course, whether a function, which can throw an exception, should be considered pure or not, is something to discuss. (And for sure, one would have to disable exceptions for elemental procedures.)

certik commented 2 years ago

I have no idea, how compilers deal wit the evaluation of complex expressions, but in current Fortran one would have to decompose the expression in its parts with maximally one error-throwing function call, then make the call, store the temporary result, make the check for the error, and then continue with the other parts of the expression.

Yes, that's exactly how it would work. I don't see a problem from the implementation perspective. I don't know if there can be some issues with the Fortran standard, if we are breaking some rule about Fortran's expression evaluation.

The biggest problem I have with this variable extending approach, that we would be not allowed to use the exception mechanism in pure functions, while pure subroutines would be no problem.

Why cannot the function by pure that uses this mechanism?

aradi commented 2 years ago

Why cannot the function by pure that uses this mechanism?

IIRC, pure functions can only have intent(in) arguments.

aradi commented 2 years ago

As for the status-proposal: I think, our current approach is superior. There is no scenario, where a program would be error stopped due to an exception. Rather, we would force the programmer to either handle the exception or propagate it upwards. Code, which does not do any of the two (e.g. which tries to ignore an exception) would be simply invalid.

If the programmer wanted to stop the code due to an exception, it would have to happen explicitly, e.g.

try catch
  call subroutine_throwing_error(...)
catch all
  error stop "Routine failed and I don't want to deal with it"
end try

All intrinsic commands/routines (allocate, open, etc.) should still use their old way of reporting errors via integer flags. But the programmer should have a way to easily propagate this error up, if wanted:

open(file="test.dat", ..., iostat=iostat)
if (iostat /= 0) throw io_error(message="Could not open file", file="test.dat")

The exception io_error is defined by the programmer, with arbitrary content, whatever makes sense in that project. The only thing forced upon the programmer is the necessity to handle/propagate errors if an error throwing procedure was invoked.

certik commented 2 years ago

Yes, I like this overall design so far. That's where a compiler comes in, to enforce that the error is handled one way or another. The way it is enforced in your library currently is that it will fail at runtime when the error object gets deallocated, which is the only way I think it can be done currently, but if it is part of the language, then it will get enforced at compile time, which I think is much better.

aradi commented 2 years ago

@certik In case, you want to prototype it in LFortran, I've found a blog entry about the error handling implementation in Swift. I think, this lightweight solution should be exactly, what we should be heading for.

Actually, thinking about Swifts strategy, we could also consider to use a simple throws clause without an explicit list of the error types thrown by the routine:

subroutine subroutine_with_error(...) throws
  ...
  throw io_error(name="somefile.dat")
 ...
end subroutine subroutine_with_error

This would then simplify interface declarations as well, as one would not have to list all the errors explicitly. And we should go with the Swift convention, that an routine, which does not throw an error, matches an interface, which allows for error throwing (but not the other way around). We should then probably also require, that every try catch structure must have a catch all clause, unless the embedding routine itself has the throws clause. That way, it remains a simple compile time decision, whether a given routine may throw an error or not.

Last, but not least, we could also easily mimic Switfs try? and try! constructs. By allowing for a try ... else ... in an assignment, we could provide an even superior alternative for their try?, where the default value is set explicitely:

! some_value contains either the return value of function_throwing_error (if no error occured) or -1 (if error occured)
some_value = try function_throwing_error() else -1

And the try! construct (which would stop in case the call throws an error), could be probably implemented with a special keyword

some_value = try_stop function_throwing_error()

The try_stop construct could also be used for subroutine calls, if the error should lead to an immediate stop:

! Would stop the code, if the subroutine has thrown an error
try_stop call subroutine_throwing_error()
certik commented 2 years ago

I think the Swift's approach is essentially like Rusts or Zigs, except that Swift handles this automatically, so the error is not exposee explicitly as a type, but the compiler does the equivalent thing: it stores the error as a return type (in a special register) and checks it in the caller.

That is a design that we can also pursue -- just add some keywords like throws, which would instruct the compiler to return the error flag (either success or with an error struct).

Notice that all these designs (Rust, Zig, Swift) have one thing in common: no long jump, no stack unwinding like traditional C++ exceptions. Just syntax sugar for returning the error as a result of a function or subroutine. They differ how the error is returned (whether explicitly, or implicitly).