j3-fortran / fortran_proposals

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

Yet another error-handling proposal #304

Open jwmwalrus opened 1 year ago

jwmwalrus commented 1 year ago

I'be been looking at some of the proposals (here) for error-handling in Fortran, and even though they're good, none of them seem to take advantage of existing Fortran idioms, but rather borrow heavily from other language(s).

One of the things I like in Fortran 2023 is the enumeration type ---which would be perfect, had it included the option for a formatted type-bound write.

Using that enumeration type as a guideline, an exception could be declared as:

module my_exceptions
    implicit none
    private

    exceptions type, public :: io_ex
        exception :: open_error, read_error
        exception :: write_error
    contains
        write(formatted) :: write_io_ex    !<-- there is no need for generic here
    end exceptions type

    exceptions type, public :: print_only
        exception :: to_error_unit
        exception :: to_log
    end exceptions type

contains
    subroutine write_io_ex(dtv, unit, iotype, v_list, iostat, iomsg)
        ...
        select case (dtv)
        case (open_error)
            write (unit, '(...)') 'error opening unit...'
        end select
    end subroutine
end module my_exceptions

With that, I think subroutines (and only a subroutines i.m.o.) could declare and "throw" exceptions like this:

module my_io
    use my_exceptions
    implicit none
contains
    subroutine sub(arg) failing with(io_ex, print_only)    !<-- annotate expected failures
        ...
        open (NEWUNIT = unit, IOSTAT = ios, ...)
        if (ios /= 0) fail with (open_error)    !<-- throw exception here
        ...
        close (unit, IOSTAT = ios)
        if (ios /= 0) fail with (to_error_unit)    !<-- thrown at the end, so failure could be ignored
    end subroutine
end module my_io

And another program unit calling the subroutine could do this:

program test
    use my_io
    use iso_fortran_env
    implicit none

    exception :: handle_ex    !<-- define the variable "catching" the exception

    call sub(arg) with (handle_ex)    !<-- without the "with (handle_ex)", the failure would propagate up the stack

    ! handling alternative one: handle by exception
    select case (handle_ex)
    case (open_error)
        print *, handle_ex
    case (to_error_unit)
        write (ERROR_UNIT, *) handle_ex    !<-- error, no formatted type-bound write
    case default
        ...
    end select

    ! alternative 2: handle by type
    select type (handle_ex)
    type is (io_ex)
        ...
    type is (print_only)
        ...
    class default
        ...
    end select
end program test

With that, the exception handling facilities could be defined by leveraging existing features, avoiding reliance on inheritance, and not having to deal with explicit error codes.

There might be some pending details though, like

And although I think a try-catch block would be unnecessary with the above, for syntactic-sugar purposes it could be something like

exception :: catcher
...
failing [ with (catcher) ]              !<-- the "with (catcher)" is optional
    call sub(arg) 
recover from (open_error, print_only)
    select case (catcher)               !<-- only possible if catcher is explicit for the failing block
    ...
    end select

    select type (catcher)               !<-- only possible if catcher is explicit for the failing block
    ...
    end select
recover from (write_error)
    ...
recover all
    ...
end failing

So, any thoughts on the above?

gronki commented 6 days ago

So, if I understand correctly, it is not really an exception (in sense that it is not thrown and could be possibly caught many levels up the call stack), but really a new syntax for an output value containing error and return from the current procedure (just like error code but more sophisticated?) that must be checked after call (like Go, Rust, Zig)?

jwmwalrus commented 5 days ago

Hi @gronki. It's been a while since I posted that (almost a year and a half).

Even though I didn't get any reaction here, I sort of kept adjusting the idea.

Fortran already has exception handling for the statements and some intrinsic subroutines (through STAT/IOSTAT, so yes, it's only one level up the stack). What the proposal does is extending that idea to user-defined impure subroutines, and more importantly, stating the expected failures in the subroutine signature.

It is more inspired by Go and Zig, than Rust.

It is also backwards compatible ---i.e., if you invoke a subroutine without the WITH suffix and a failure occurs, it crashes, just like any statement without STAT/IOSTAT. And if your subroutine signature doesn't have a FAILING WITH, then you cannot use FAIL [AGGREGATE(...)] WITH, so it behaves in the traditional way.

Here's the latest iteration (intended as *.txt, hence the keywords in upper-case):

-----8<-----

Introduction

Although there is already a proposal for error-handling in Fortran, that one focuses on mimicking C++-like error handling (further propagated by Java, C# and the like).

This proposal focuses on extending the strengths of Fortran, and also following the error-as-data trend applied in recent languages like Go, Rust and Zig.

Fortran makes a side-effect based distinction between functions and subroutines, and the intrinsic procedures tend to show it ---i.e., almost all the intrinsic functions are pure, and almost all the intrinsic subroutines are non-pure.

Both the intrinsic subroutines and the side-effect related statements (e.g., OPEN, ALLOCATE, etc.) provide both a STAT/IOSTAT integer value and an ERRMSG/IOMSG character string value to indicate that an error has occurred. Even though both values are separate, they occur in tandem ---e.g., a significant IOMSG character string cannot occur without a non-zero IOSTAT value.

This proposal centers on the fact that user-defined error handling should provide that same pattern, be applicable only to impure subroutines, and make the possibility of error explicit in the subroutine's signature.

The proposed error-handling facility is based upon

Additionally, although not limited to exceptions, in order to provide the possibility of cleanup, a DEFER CALL statement is also proposed.

Components

An EXCEPTIONS GROUP defines an enumerated sequence of EXCEPTION values. Each EXCEPTION value in an EXCEPTIONS GROUP consists of a STAT and an ERRMSG. The default STAT value for an EXCEPTION follows the ENUMERATION rules. The default ERRMSG value is an empty string.

The following illustrates the definition of an EXCEPTIONS GROUP:

MODULE my_exceptions

    EXCEPTIONS GROUP, PUBLIC :: io_ex_g('io-ex')                ! 'io-ex' is the group name
        EXCEPTION :: open_error, read_error                     ! STAT is 1 and 2, respectively. Default ERRMSG is '' for both
        EXCEPTION :: write_error = (4, 'failed to write')       ! STAT=4, default ERRMSG='failed to write'
        EXCEPTION :: endfile_error                              ! STAT = 5
        EXCEPTION :: close_error = (ERRMSG = 'failed to close') ! STAT = 6, default ERRMSG='failed to close'
        EXCEPTION :: other_error = 7                            ! STAT = 7
    END EXCEPTIONS GROUP io_ex_g

    EXCEPTIONS GROUP, PUBLIC :: print_ex_g('print-ex')
        EXCEPTION :: error_unit_error = (STAT = 42, ERRMSG = 'something went wrong')
    END EXCEPTIONS GROUP print_ex_g

END MODULE my_exceptions

Under the hood, each EXCEPTION statement within an EXCEPTIONS GROUP behaves like the definition of a different derived type that has only STAT and ERRMSG as components.

There is also the EXCEPTIONS statement, to hold any exceptions thrown during a call. An EXCEPTIONS variable is defined as:

EXCEPTIONS :: var_name

An impure subroutine can declare that it may fail with a given exceptions group through the FAILING WITH suffix annotation, and throw the corresponding exception with the FAIL WITH statement

MODULE my_mod
    USE my_exceptions

    IMPLICIT NONE

CONTAINS
    SUBROUTINE sub1(arg) FAILING WITH(io_ex_g, print_ex_g)  !<-- annotate expected failures
        ...
        OPEN (NEWUNIT = unit, FILE = file, IOSTAT = ios, ...)
        IF (ios /= 0) FAIL WITH (open_error, 'there was an error opening file '//TRIM(file))  !<-- throw exception here,
                                                                                                  !    override default ERRMSG
        ...
        WRITE (unit, IOSTAT = ios, ...) some_var
        IF (ios /= 0) FAIL WITH (write_error)    !<-- throw exception here, with default ERRMSG
        ...
        CLOSE (unit, IOSTAT = ios, IOMSG = iomsg)
        IF (ios /= 0) THEN
            WRITE (ERROR_UNIT, '(1x,a)', IOSTAT = ios) TRIM(iomsg)
            IF (ios /= 0) FAIL WITH (error_unit_error)
        ENDIF
    END SUBROUTINE  sub1
END MODULE my_mod

An exception is guaranteed to be caught by the caller, by explicitly stating so through the WITH(...) suffix in a CALL statement. It can then be handled with a simple IF construct, as follows

USE my_mod

IMPLICIT NONE

INTEGER :: i
INTEGER, ALLOCATABLE :: nums(:)
CHARACTER(255), ALLOCATABLE :: groups(:), msgs(:)
EXCEPTIONS :: err

CALL sub1('') WITH(err)
IF (FAILED(err)) THEN                                        !<-- use of the FAILED generic intrinsic function
    CALL GET_EXCEPTIONS(err, GROUP = groups, STAT = nums, ERRMSG = msgs)    !<-- intrinsic subroutine to obtain aggregate error values
    DO i = 1, SIZE(groups)
        WRITE (ERROR_UNIT, *) TRIM(groups(i)), ' error ', nums(i), ': ', TRIM(msgs(i))
    ENDDO
ENDIF

END

Or it can also be handled by using the SELECT EXCEPTION construct after the call statement

USE my_mod

IMPLICIT NONE

INTEGER, ALLOCATABLE :: nums(:)
CHARACTER(255), ALLOCATABLE :: msgs(:)
EXCEPTIONS :: err

CALL sub1(arg) WITH (err)
SELECT EXCEPTION (err)            !<-- behavior is similar to SELECT TYPE
EXCEPTION (open_error, write_error)
    CALL GET_EXCEPTIONS(err, STAT = nums, ERRMSG = msgs)
    ...
EXCEPTION (close_error)
    CALL GET_EXCEPTIONS(err, ERRMSG = msgs)
    ...
EXCEPTION DEFAULT                !<-- There is at least an exception, but it is not listed as an exception case
    STOP 'Unhandled exception'
EXCEPTION NONE                    !<-- There were no exceptions
    PRINT *, 'No error occurred during the call'
END SELECT

END

The use of the SELECT EXCEPTION construct mimics the workflow of a try-catch in other languages, although it is not forced on the programmer.

Thrown exceptions can be aggregated, and the subroutine signature can have a catch-all annotation:

MODULE other_mod
    USE my_mod

    IMPLICIT NONE

CONTAINS
    SUBROUTINE sub2(arg) FAILING WITH(*)    !<-- annotates any failure
        EXCEPTIONS :: ex
        ...
        CALL sub1(arg) WITH(ex)
        if (FAILED(ex)) FAIL AGGREGATE(ex) WITH (my_custom_error, 'extra info ...') !<-- adds extra info to thrown exception
    END SUBROUTINE
END MODULE other_mod

Some compile-time error scenarios:

MODULE ct_mod
    USE my_mod
    USE my_custom_mod

    IMPLICIT NONE

CONTAINS
    SUBROUTINE sub3(arg)
        EXCEPTIONS :: ex
        ...
        CALL sub1(arg) WITH(ex)
        IF (FAILED(ex)) FAIL WITH (my_custom_error) !<-- compile error, no annotation in sub3 subroutine signature
    END SUBROUTINE

    SUBROUTINE sub4(arg) FAILING WITH(io_ex_g)
        EXCEPTIONS :: ex
        ...
        CALL sub1(arg) WITH(ex)
        IF (FAILED(ex)) FAIL WITH (my_custom_err) !<-- compile error, exception not in sub4 subroutine signature
    END SUBROUTINE
END MODULE ct_mod

Cleanup

In some cases, it is desirable to perform some cleanup tasks after failure, but right before returning to the caller. For that, the DEFER CALL statement can be used. It effectively schedules the invocation of a subroutine right before it returns to the caller.

MODULE my_mod
    USE my_exceptions

    IMPLICIT NONE

CONTAINS
    SUBROUTINE sub1(arg) FAILING WITH(io_ex_g, print_ex_g)
        REAL, POINTER :: arg(:)
        ...
        ALLOCATE (arg(5))
        ...
        DEFER CALL cleanup()

        OPEN (NEWUNIT = unit, FILE = file, IOSTAT = ios, ...)
        IF (ios /= 0) FAIL WITH (open_error, 'there was an error opening file '//TRIM(file))
        ...
        WRITE (unit, IOSTAT = ios, ...) some_var
        IF (ios /= 0) FAIL WITH (write_error)
        ...
        CLOSE (unit, IOSTAT = ios, IOMSG = iomsg)
        IF (ios /= 0) THEN
            WRITE (ERROR_UNIT, '(1x,a)', IOSTAT = ios) TRIM(iomsg)
            IF (ios /= 0) FAIL WITH (error_unit_error)
        ENDIF

    CONTAINS
        SUBROUTINE cleanup()
            IF (FAILED()) THEN    !<-- This version of the generic intrinsic can only be called from within a contained
                                  !    subroutine in which the parent scope has the FAILING WITH suffix annotation
                IF (ALLOCATED(arg)) DEALLOCATE (arg)
                NULLIFY (arg)
            ENDIF
        END SUBROUTINE
    END SUBROUTINE  sub1
END MODULE my_mod

The DEFER CALL statement is not limited to exception handling and CONTAINed subroutines. It can also aid in some other cases, e.g., in reporting.

MODULE my_mod
    USE loggers
    IMPLICIT NONE

CONTAINS
    SUBROUTINE solve(A, b, x)
        REAL, INTENT(IN) :: A(:,:)
        REAL, INTENT(IN) :: b(:)
        REAL, INTENT(OUT) :: x(SIZE(b))
        INTEGER :: solution_type
        ...
        CALL announce(A, b)
        DEFER CALL report(solution_type, x)
        ...
        ! Perform computations
        ...
    END SUBROUTINE

    SUBROUTINE announce(A, b)
        REAL, INTENT(in) :: A(:,:)
        REAL, INTENT(in) :: b(:)
        CALL logger%info(...)
    END SUBROUTINE

    SUBROUTINE report(solution, x)
        INTEGER, INTENT(in) :: solution
        REAL, INTENT(in) :: x(:)
        CALL logger%info(...)
        SELECT CASE (solution)
        ...
        END SELECT
    END SUBROUTINE
END MODULE my_mod

If multiple DEFER CALL statements are issued within a subroutine subprogram, they shall be invoked in reverse order.

CONTAINed impure subroutines

CONTAINed subroutines cannot have the FAILING WITH(...) annotation. The FAIL [AGGREGATE (...) ] WITH statement can be invoked from a CONTAINed subroutine, effectively (aggregating and) ending the parent subroutine's invocation.

SUBROUTINE sub4(a, b, c) FAILING WITH (some_ex_g)
    ...
CONTAINS
    SUBROUTINE compute(num, denom)
        ...
        IF (denom == 0) FAIL WITH (div_by_zero, 'computation not allowed') !<--makes sub4 invoke any deferred calls and
                                                                              !   return to the caller
        ...
    END SUBROUTINE
END SUBROUTINE

Non-CONTAINed impure subroutines

A DEFER CALL to a non-CONTAINed impure subroutine can have the WITH(...) suffix, but any exceptions occurred during the deferred invocation are only aggregated to the parent scope EXCEPTIONS if the EXCEPTION GROUPs are compatible.

Statements and Intrinsics

Statements that return STAT/IOSTAT and ERRMSG/IOMSG values, can provide an optional INTENT(INOUT) EXCEPTIONSargument. This has the potential benefit of returning much more detailed information.

EXCEPTIONS :: ex
...
OPEN (FILE = 'some.data', ..., EXCEPTIONS = ex, ...)
IF (FAILED(ex)) THEN
    CALL GET_EXCEPTIONS(STAT = nums, ERRMSG = msgs)  !<-- multiple messages can be returned
    ...
    ERROR STOP 1
ENDIF
...
END

Impure intrinsic subroutines that return STAT/IOSTAT and ERRMSG/IOMSG values can be invoked with the WITH(...) suffix:

EXCEPTIONS :: ex
...
CALL CO_BROADCAST (A, srcimg) WiTH (ex)
...
END

----->8-----