I have a toy project about designing a very simplified exception system in Fortran that imitates Python's exceptions. Until now, it appears to work, but I stumbled upon an inconvenience. I must say that I do not have as much experience with Fortran as with Python. I can read Fortran and write code for patching or extending old projects following examples from the existing code. Never before I have used Fortran as an object-oriented language.
I have defined an abc_exceptions module, where I define the abstract base "class" for the exceptions. There, I define an abstract interface to a subroutine some type-bound methods for providing, e.g., the display name of derived "classes" (such as ValueError) or the implmentation of a rudimentary backtrace stack. Additionally, I define three subroutines that raise exceptions using a certain mold, adding the error location information, rethrow exceptions, and show the backtrace stack before handling the exception or calling for a stop of the program after showing the backtrace. Additionally I define another module with concrete "classes" derived from the abstract base class (in Python parlance).
As I said, so far so good, but in the test I found that I need to import the exception base "class" to be able to raise an exception for the first time and pass it for further handling. On compile time, I get an error when I try to pass a derived type object to the optional class(exception), intent(out) argument error:
That means when I define err at the beginning as
class(value_error), allocatable :: err
and pass it to the raise subroutine
call raise( &
except=value_error("bad input"), &
offending_file="parser.f90", &
offending_line=10, &
offending_procedure="parse", &
offending_module="parsers", &
error=err &
)
I get
21 | error=err &
| 1
Error: Actual argument to 'error' at (1) must have the same declared type
if I change to class(exception), allocatable :: err everything works as expected
The program is the following
program test_exceptions
!!! Test the prototype for very basic Python-like exceptions in Fortran
!!!
!!! This is the first try
use abc_exceptions, only: exception
use exceptions, only: value_error, raise, rethrow, failed
implicit none
class(value_error), allocatable :: err
! Level 1: Create exception, add manually error location information and prepare
! for external handling
call raise( &
except=value_error("bad input"), &
offending_file="parser.f90", &
offending_line=10, &
offending_procedure="parse", &
offending_module="parsers", &
error=err &
)
! Level 2: Rethrow and add more context
if (failed(err)) then
call rethrow( &
err, &
offending_file="driver.f90", &
offending_line=42, &
offending_procedure="run", &
offending_module="main_driver" &
)
end if
! Print error string up to this point
if (failed(err)) then
write(*, "(A)") trim(err%string())
! Expected:
! ValueError: bad input
! @ parser.f90:10 in parse ->
! driver.f90:42 in run
end if
! Raise again without new information and without the optional `error` leading to stop
call raise(except=err)
end program test_exceptions
and the signature and declaration part of the raise subroutine is
subroutine raise( &
except, &
offending_file, offending_line, offending_procedure, offending_module, error &
)
!!! Raise an exception and propagate the error
!!!
!!! This subroutine allocates an exception and raises it to be handled or aborts
!!! the program execution emitting the error message related to the exception
implicit none
class(exception), intent(in) :: except
!!! An exception class used as mold or for issuing the error message
character(*), intent(in), optional :: offending_file
!!! File name where the exception is raised
integer, intent(in), optional :: offending_line
!!! Line of the offending file where the exception is raised
character(*), intent(in), optional :: offending_procedure
!!! Procedure where the exception is raised
character(*), intent(in), optional :: offending_module
!!! module where the exception is raised
class(exception), allocatable, intent(out), optional :: error
!!! Exception that will be allocated, propagated and handled elsewhere
This fact that the argument class(exception), intent(in) :: except accepts a value_error derived type, makes me wonder if the intent(out) is for some reason limited. What are your thoughts on this? What are possible solutions to this problem if there is any limitation about intent(out) and polymorphic objects or is the problem my inexperience with Fortran only?
More details on the implementation
- Abstract Base Class
module abc_exceptions
!!! Module implementing abstract base classes for defining exceptions
!!!
!!! This module defines an abstract base classes for having exception handling
!!! capabilities in Fortran
use auxiliary_tools, only: print_integer, join
implicit none
private
type, abstract :: exception
!!! Abstract base class defining an exception
!!!
!!! It defines an abstract base class from which concrete exceptions inherit. It
!!! specifies attributes as well as needed methods with as blueprints with no
!!! implementation
!!!
!!! @note
!!! Here the **class** concept is not Fortran parlance. The appropriate Fortran
!!! concept is **type**
!!! @endnote
!!!
!!! @note
!!! Here the **attribute** and **method** concepts are Python parlance. The
!!! appropriate Fortran concepts are **type member** and **type-bound procedure**.
!!! The blueprints of the type-bound procedures are **(abstract) interfaces**
!!! @endnote
character(:), allocatable :: error_message
!!! Error message displayed when an exception is raised
character(:), allocatable, private :: location_of_error(:)
!!! Information on the location of the error. This is a pile of error
!!! locations so that one can obtain a simple traceback
contains
procedure(exception_tag), deferred :: tag
!!! Mandatory method to be implemented in all concrete classes for giving a
!!! name to the exception
procedure :: string => exception_string
!!! Method with a concrete implementation given by
!!! [[abc_exceptions:exception_string]]
procedure :: push_location
!!! Method for adding information to the `location_of_error`
procedure :: get_location
!!! Method for getting the information in `location_of_error`
end type exception
abstract interface
pure function exception_tag(self) result(exception_name)
!!! Method blueprint for setting the exception name
!!!
!!! The blueprint only specifies what should be expected of a method that sets
!!! the name of a concrete exception. Implementation should be given in the
!!! concrete exceptions
import :: exception ! Import into this scope the abstract base class
implicit none
class(exception), intent(in) :: self
character(:), allocatable :: exception_name
!!! The tag of the exception
end function exception_tag
end interface
public :: exception, raise, rethrow, failed
apart from defining the blueprint of the tag method in the contains part of the module as well as methods for printing the backtrace, pushing new backtrace entries when rethrowing, I define the subroutines raise, rethrow and failed, which habe the following declarations
subroutine raise( &
except, &
offending_file, offending_line, offending_procedure, offending_module, error &
)
!!! Raise an exception and propagate the error
!!!
!!! This subroutine allocates an exception and raises it to be handled or aborts
!!! the program execution emitting the error message related to the exception
implicit none
class(exception), intent(in) :: except
!!! An exception class used as mold or for issuing the error message
character(*), intent(in), optional :: offending_file
!!! File name where the exception is raised
integer, intent(in), optional :: offending_line
!!! Line of the offending file where the exception is raised
character(*), intent(in), optional :: offending_procedure
!!! Procedure where the exception is raised
character(*), intent(in), optional :: offending_module
!!! module where the exception is raised
class(exception), allocatable, intent(out), optional :: error
!!! Exception that will be allocated, propagated and handled elsewhere
! Local variables
character(:), allocatable :: loc
subroutine rethrow( &
error, &
offending_file, offending_line, offending_procedure, offending_module &
)
!!! Re-Raise an exception and propagate the error
!!!
!!! This subroutine takes an existing exception adding backtracing information and
!!! rethrowing it.
implicit none
class(exception), intent(inout) :: error
!!! Allocated exception for which we will add backtracing and will be rethrown
character(*), intent(in), optional :: offending_file
!!! File name where the exception is raised
integer, intent(in), optional :: offending_line
!!! Line of the offending file where the exception is raised
character(*), intent(in), optional :: offending_procedure
!!! Procedure where the exception is raised
character(*), intent(in), optional :: offending_module
!!! module where the exception is raised
! Local variables
character(:), allocatable :: loc
pure function failed(exception_candidate) result(raised)
!!! Test if a certain candidate exception was raised
!!!
!!! @note
!!! In this framework, a raised exception means that the exception is actually
!!! allocated. Then the pattern is that one will use allocatable exception objects
!!! when an exception needs to be raised ([[abc_exceptions:raise]]), the exception
!!! is allocated
!!! @endnote
implicit none
class(exception), allocatable, intent(in) :: exception_candidate
!!! Exception to check whether it was raised
logical :: raised
!!! Whether the exception candidate has been raised
raised = allocated(exception_candidate)
end function failed
- Concrete exception module
Here I use the ABC as well as the three subroutines for raising, rethrowing and the failed function. They do not have a new implementation particularised for the concrete class. Additionally, I implement the tag method for the value_error class, as well as the constructor. All other things are inherited from the ABC. I expose value_error as well as raise, rethrow and failed from the ABC
module exceptions
!!! Module for concrete exceptions
!!!
!!! This module defines concrete exceptions as subclasses of
!!! [[abc_exceptions:exception]]
use abc_exceptions, only: exception, raise, rethrow, failed
implicit none
private
type, extends(exception) :: value_error
!!! Class of exceptions when there is a value error
!!!
!!! A value error is raised when a variable should fulfill certain conditions and
!!! these conditions are not satisfied. Therefore, the variable is invalid in this
!!! context
contains
procedure :: tag
end type
interface value_error
!!! Interface to the constructor of the concrete class
module procedure init_
end interface
public :: value_error, raise, rethrow, failed
contains
pure function init_(message) result(new_exception)
!!! Constructor of the value error exceptions
implicit none
character(*), intent(in) :: message
!!! Error message that the exception will display if it is raised but not
!!! propagated to be handled
class(value_error), allocatable :: new_exception
!!! New instance of the exception [[value_error_exceptions:value_error]]
allocate(new_exception)
new_exception%error_message = message
end function
pure function tag(self) result(name)
!!! Concrete implementation of the abstract method [[abc_exceptions:tag]]
!!!
!!! This function will return the exception name of
!!! [[exceptions:value_error]]
implicit none
class(value_error), intent(in) :: self
character(:), allocatable :: name
!!! Name of this concrete exception
name = "ValueError"
end function
end module exceptions
In principle, I would expect that any argument that is declared as class(exception) (no matter the intent) will be taken when coming from value_error: subtype of exception.
class(exception), intent(in) :: exceptandclass(exception), allocatable, intent(out), optional :: erroris not the different intent, but that one is allocatable and one is not. "Allocatable" and "not allocatable" is a huge difference.raiseusing the following code ``` if (present(error)) then allocate(error, source=except) ! The output exception is allocated... if (len(loc) > 0) then call error%push_location(loc) ! ...and the location is set end if ... ``` thus, iferrorexists, the output argument will be a (deep?) copy of except. Is there a way to indicate the situation in the declaration so that compiler gets it?