Error handling landscape

I recently read this blog post:

Parse, don’t validate

Which especially @everythingfunctional will enjoy (examples in Haskell!). It’s worth the read, and it lead me to the following idea regarding error handling: I think there are two ways to handle errors in functions:

  • Weaken the result (Rust Result, C++ optional, Haskell Maybe)
  • Strengthen the input arguments (create a special type that prevents the error input to be passed in by the type system at compile time)

The second approach is what the blog post above argues for, and that is also this proposal for Fortran: Assert by wclodius2 · Pull Request #177 · j3-fortran/fortran_proposals · GitHub. The first approach is what the various proposals in the Exceptions proposal discussion try to address.

And I think we need both. Let me give examples.

Example where the second approach is better

This example was given in the “exceptions thread”:

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

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

The issue is about how to handle the case where size(vals) == 0. One can use both approaches here, one can use the first approach and weaken the result by changing real :: mean to real, optional :: mean or by throwing an exception. However, in this case I think the second approach is better:

pure function mean(vals)
  real, intent(in) :: vals(:)
  require :: size(vals) > 0
  real :: mean

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

This strengthens the type of the function “mean” to include this requirement. The compiler then refuses to even compile your code unless it can ensure at compile time that the argument val has nonzero size. So a = mean([1., 2., 3.]) will compile and is guaranteed to always work. a = mean([]) will not compile. a = mean(x) will compile only if x is declared with the requirement require :: size(vals) > 0 in the parent function. If it is not and it cannot be inferred that it is nonzero size, it will not compile. You then propagate this requirement all the way up. Say if you read the array from a file into an array that is declared with this requirement, the compiler can ensure at the reading from the file that the requirement is met (at runtime).

This approach even works for bounds checking for things like CSR arrays:

function csr_matvec(Ap, Aj, Ax, x) result(y)
! Compute y = A*x for CSR matrix A and dense vectors x, y
integer, intent(in) :: Ap(:), Aj(:)
real(dp), intent(in) :: Ax(:), x(:)
require :: all(1 <= Ap) .and. all(Ap < size(Ax)) .and. all(1 <= Aj) .and. all(Aj <= size(x))
real(dp) :: y(size(Ap)-1)
integer :: i
do i = 1, size(Ap)-1
    y(i) = dot_product(Ax(Ap(i):Ap(i+1)-1), x(Aj(Ap(i):Ap(i+1)-1)))
end do
end function

The requirements are not 100%, but you get the idea, it is possible to exactly specify all the conditions so that the function never fails bounds checking, so the compiler in ReleaseSafe mode (all optimizations on, all bounds checking still on) does not have to bounds check, only check the requirements (at compile time).

If the CSR array is read from a file, it might still be relatively cheap (although not free) to check if the arrays satisfy the requirement in ReleaseSafe and Debug mode, and one can ignore it in Release mode. The beauty of this approach is that it shifts all these bounds checks from inner loops to the main program, and thus ReleaseSafe could run at the same speed as Release, while guaranteeing it will not segfault. The compiler could even ensure that every time you index into an array, there is an appropriate requirement set, so that it can guarantee at compile time that no bounds errors will happen (it is not clear to me if this is possible every time, perhaps only for functions which you declare with “enforce requirements”).

Example where the first approach is better

pure function solve(A, b) result(x)
  real, intent(in) :: A(:,:), b(:)
  real :: x(size(b))
  x = ... ! call Lapack to solve the system A*x = b.
end function

Here we could insert a requirement require :: "inv(A) exists", but clearly determining if the solve will succeed is as much work as doing the solve itself, it’s not a simple condition to check like in the previous cases above. For example if you read the matrix from a file, it’s not easy to check that it satisfies the condition, without actually doing the solve, which is expensive. I can actually see some simple applications where this might be ok to do, you’ll pay the price up front, and then don’t have to worry about any error checking later and it is guaranteed to work, but in general this approach will not work here.

Rather, we need to weaken the result, for example something along these lines:

pure function solve(A, b) result(x)
  real, intent(in) :: A(:,:), b(:)
  real, optional :: x(size(b))
  x = ... ! call Lapack to solve the system A*x = b.
  ! If lapack returns an error, simply return "None"
end function

Or raise an exception, which at some level is equivalent, it’s a way the function can return “None”. But then this new “return state” must be handled in the caller. So there is extra work to be done, it’s slower than the second approach, however, since solve is an expensive operation (which is the very thing that makes the second approach not feasible), it is not a big deal to do these extra checks at runtime.

Conclusion

It seems to me that if the requirements are cheap to compute, then the second approach is better, since it eliminates any error handling at runtime. If the requirements are costly to compute, the first approach is better, and we need to handle the error at runtime: but ideally the compiler would still enforce at compile time that we always handle the error state.

3 Likes

I like the requirements from a style perspective. I’m confused what you meant in the above quote. In what situation will the compiler compile the program, but need to check for the requirements at run-time? It seems to me that for most real-world use cases run-time checks will be necessary.

Here is an example:

real, allocatable :: x(:)
require :: size(x) > 0 ! let's assume it's allocated for now
print "(a)", "Loading the model..."
open(newunit=u, file="model.dat", form="unformatted", access="stream", status="old")
read(u) n
allocate(x(n))
read(u) x ! here the compiler will check that `size(x) > 0` at runtime and "error stop" otherwise
close(u)

print *, mean(x) ! is guaranteed to always work at runtime, no checks needed

I guess the check would happen already at the allocate(x(n)) line. It must be both allocated and nonzero size. We would have to figure out these details, but you get the idea hopefully what I mean.

Dependent Types, for example, types that carry around a length attribute, can solve this kind of problem in a disciplined way. The controlling examples in Chaper 6 of “The Little Typer,” for instance, include Vec types that bottom out at zero length – in the types of both functions and arguments see my redux of Chapter 6. I know Fortran is not ML, Haskell, or Lisp, but type theory ought to be similar across the languages.

2 Likes

OK. So it seems to me, what you meant is that the compiler will always compile mean(), even when it can’t determine that the requirement will be satisfied, but the program will then be required to check the requirement at run-time prior to invoking mean(). Did I understand this correctly?

@certik, will there be any overarching “principle” that will guide the design of such error handling? Such as what C++ strives with “zero-overhead”? And for which there is reasonable consensus amongst that community that their current exceptions feature does not follow.

I ask because what you suggest in your original post does appear more like run-time checks (e.g., your size > 0 “requirement”) and there will be some cost associated with it that one has to “pay for” even when one is not using it.

The compiler will always compile mean, but it would not allow it to be called unless it can guarantee the requirement (at compile time), which would be treated as part of the function type of mean. No runtime checking.

The only runtime checking happens when you want to cast an array without a requirement to an array with a requirement of size(x) > 0, which would typically happen in the main program or high up in the stack. The actual computational algorithm will have no runtime checking.

To make the example correct, here is how one can do it:

real, allocatable :: x(:)
print "(a)", "Loading the model..."
open(newunit=u, file="model.dat", form="unformatted", access="stream", status="old")
read(u) n
allocate(x(n))
read(u) x
close(u)
print *, mean(x) ! would not compile
print *, mean(ensure_requirement(x)) ! inserts runtime check, explicitly

In practice, you would have tons of functions like:

pure real function f(vals)
  real, intent(in) :: vals(:)
  require :: size(vals) > 0
  f = mean(vals) * 5 ! no runtime checking, always compiles and is guaranteed to work
end function

And it runs at full speed (no runtime checks) and it is guaranteed to work, by construction. Only in the main program or high up in the stack you must “ensure the requirement holds”, for example by ensure_requirement(x), which converts x from a regular array, to an array with the requirement size(x) > 0 added.

I hope I clarified it in my previous comment. The second approach has no hidden runtime cost (the cost is explicit in the ensure_requirement(x) which happens high up in the call stack, not in computational code — and this cost only happens in ReleaseSafe mode; there is no runtime cost in Release mode, but the code could then segfault) . The first approach has a runtime cost, depending on the exact mechanism of the error handling.

I am familiar with ideas in that blog post, and am generally a fan of them. I will say that following those patterns in Fortran is already possible. You’ll see those patterns if you look in my libraries. For

We already have derived types, so you can absolutely do this. No need for the extra requires attribute or statement. It might be repetitive (until generics) for cases like NonEmpty a, but it is doable. For

You absolutely can model this with derived types, in fact for those of you who have seen my “fallible” pattern, which is well supported by rojff, and used heavily when I make use of it, its design was influenced by Haskell’s Either type.

I’ll note here, that at the places that you “strengthen the input arguments” you will often see the function that does the conversion (i.e. from [a] to NonEmpty a) use the “weaken the result” pattern for it’s return type (i.e. [a] -> Either Error (NonEmpty a)).

I will note though, that the “weaken the result” pattern does incur some overhead all the way up the call stack until the point that actually deals with the error condition. I.e. you end up with something like

maybe_intermediate = foo(...)
if (maybe_intermediate%failed()) then
  res = failed(maybe_intermediate%error())
  return
else
  intermediate = maybe_intermediate%answer()
  ...
end if

The idea with something like exceptions is that you can potentially avoid the intermediate overhead, both in terms of the lines of code needed and the actual run time logical check and extra object construction and extraction. Instead the control flow can jump from the point the exception is encountered to the point the exception is handled, with very low overhead (possible none?) if no exception is encountered. I’ll admit I’m not familiar with all the details of how exception handling is implemented or the various strategies for doing so, but I do believe it is possible for them to incur less overhead than the “weaken the result” pattern. I understand that was for some reason not the case in C++, but Fortran isn’t exactly C++, and has an opportunity to not make that same mistake.

3 Likes