Ever since I started learning Fortran many years back I’ve experimented with different ways of handling error scenarios in Fortran code. I’d like to share my latest iteration with you which is a method that I’ve found very useful and flexible. It is based on similar ideas to what you’ll see in many Rust error handling libraries like Eyre.
The code is put in a library which is easy to use both with fpm and CMake: GitHub - SINTEF/fortran-error-handling: A library for flexible and easy to use error handling in Fortran projects
The library fulfills what I believe is four essential requirements for any error handling method in Fortran:
- It should be possible to report errors from both pure and impure procedures (pure functions will always be a bit of a hassle until we have proper generics though).
- Errors should be difficult to overlook. It should be obvious for the developer that they need to check if something went wrong after calling a procedure.
- It should be easy to provide accurate information about what failed and when it occurred.
- It should be possible to make certain error situations programmatically identifiable. That is, the caller of a procedure should be able to programmatically detect and act if a certain error occurred.
Usage
General (non-identifiable) errors are easily created with a message explaining what happened:
use error_handling, only: error_t, fail
pure subroutine check_and_accumulate(i, res, error)
integer, intent(in) :: i
integer, intent(inout) :: res
class(error_t), allocatable, intent(inout) :: error
if (res > 50) then
error = fail('Magic limit reached')
return
end if
res = res + i
end subroutine
The wrap_error
subroutine makes it easy to add contextual information from other layers of the code (complete example here):
use error_handling, only: error_t, wrap_error
pure subroutine process_array(arr, res, error)
integer, intent(inout) :: arr(:)
integer, intent(out) :: res
class(error_t), allocatable, intent(inout) :: error
integer :: i
character(len=20) :: i_value
! Here we use a labelled block to separate multiple fallible procedure calls
! from the code that handles any errors
res = 0
fallible: block
do i = 1, size(arr)
call accumulate_and_check(arr(i), res, error)
if (allocated(error)) exit fallible
end do
! Return for subroutine on success, code below is only for
! error handling so no allocated(error) check is needed there.
return
end block fallible
! Provide some context with error
write(i_value, *) i
call wrap_error(error, 'Processing of array failed at element ' &
// trim(adjustl(i_value)))
end subroutine
The result is a quite human readable error message:
Error: Example failed (but that was the intent...)
Caused by:
- Processing of array failed at element 9
- Magic limit reached
It is even extensible so that if you have a C++ compiler at hand you can use my other library to generate stacktraces for errors (code snippets are only available on the machine with the source code):
Error: x is negative
Stack trace (most recent call last):
#6 Object "", at 0xffffffffffffffff, in
#5 Object "build/linux-intel/debug/example/error-handling-integration", at 0x408ded, in _start
#4 Object "/lib/x86_64-linux-gnu/libc.so.6", at 0x7f92b3c7e082, in __libc_start_main
#3 Object "build/linux-intel/debug/example/error-handling-integration", at 0x408ee1, in main
#2 Source "example/error-handling-integration.f90", line 76, in MAIN__
73: program error_handling_integration
74: use error_handling_integration_example, only: run
75:
> 76: call run
77: end program
78:
#1 Source "example/error-handling-integration.f90", line 60, in error_handling_integration_example::run
57: write(*,*) ' - sqrt = ', x
58: write(*,*) 'computing square root...'
59: x = - 20.0
> 60: call sqrt_inplace(x, error)
61: if (allocated(error)) exit fallible
62: write(*,*) ' - sqrt = ', x
63: ! Return from subroutine on success, code below is only for
#0 Source "example/error-handling-integration.f90", line 16, in sqrt_inplace_mod::sqrt_inplace
13: class(error_t), allocatable, intent(inout) :: error
14:
15: if (x <= 0.0) then
> 16: error = fail('x is negative')
17: return
18: end if
19: x = sqrt(x)
Details
At it’s core, the library uses a very simple definition of what an error is:
type, abstract :: error_t
contains
procedure(to_chars), deferred :: to_chars
end type
abstract interface
!> Returns a human readable description of the error
pure function to_chars(this) result(chars)
import error_t
class(error_t), intent(in) :: this
character(len=:), allocatable :: chars
end function
end interface
The base error type can be extended in order to make specific failures identifiable:
use error_handling, only: error_t
type, extends(error_t) :: no_such_folder_error_t
contains
procedure :: to_chars => no_such_folder_to_chars
end type
type, extends(error_t) :: permission_denied_error_t
contains
procedure :: to_chars => permission_denied_to_chars
end type
!...
And then use select type
to check for the returned type:
use error_handling, only: error_t
class(error_t), allocatable :: error
call create_file('path/to/file.txt', error)
if (allocated(error)) then
select type(error)
type is (no_such_folder_error_t)
! Try to create directory and then create the file again
! ...
end select
end if
Further Work
An abstract error_t
would be much more useful if libraries based their own error types off it. I think the Fortran community would benefit from having a small common library which defined types like this, say github.com/fortran-lang/std-types or something similar (that link does of course not exist…). When everyone derive from the same error type one could for example write code like this without having to think about type conversions for each library’s error type:
subroutine read_input(filename, error)
character(len=*), intent(in) :: filename
class(error_t), intent(out) :: error
if (ends_width('.json', filename)) then
! Imaginary call to json-fortran, jsonff or other json library
block
type(json_value_t) :: json
! This subroutine could create a json_error_t for ´error´, but since
! it extends error_t we can seamlessly pass it upwards
call read_json(filename, json, error)
if (allocated(error)) return
! Continue parsing...
end block
else if (ends_with('.toml', filename)) then
! Imaginary call to toml-f
block
type(toml_value_t) :: toml
! This subroutine could create a toml_error_t for ´error´, but since
! it extends error_t we can seamlessly pass it upwards
call read_toml(filename, toml, error)
if (allocated(error)) return
! Continue parsing...
end block
else
error = fail('Unsupported file suffix')
end if
end subroutine