In this situation, unless STAT
is nonzero, there will no reason to reference ERRMSG
at all and which is the case with intrinsic procedures (and statements),
I was thinking of a particular type of functions. See this little program:
! chk_log.f90 --
! Check what happens if you use log or sqrt on a negative value
!
program chk_log
implicit none
real :: x
integer :: i
do i = -5, 5
x = 0.1 * i
write(*,*) sqrt(x), log(x)
enddo
end program chk_log
Believe it or not, its output with (one version of) gfortran is:
NaN NaN
NaN NaN
NaN NaN
NaN NaN
NaN NaN
0.00000000 -Infinity
0.316227764 -2.30258512
0.447213590 -1.60943794
0.547722578 -1.20397282
0.632455528 -0.916290700
0.707106769 -0.693147182
and apart from the number of decimals, built with Intel Fortran it produces the very same output.
Fortran intrinsic functions (earlier, before stdlib
, sometimes referred to as, using C analogy, Fortran standard library) do that on daily basis, thus signalling EDOM error.
Just adding a bit of self-promotion for an error handling library that I wrote a while back: GitHub - samharrison7/fortran-error-handler: Comprehensive error framework for applications requiring functional and robust error handling, utilising the power of modern object-oriented Fortran.. Itās quite comprehensive (i.e. overly complex), so might be overkill here, but some of the concepts are similar to what is being discussed.
It goes down the returning a derived type path, mainly because I was new to Fortran when I wrote it and returning values via routine arguments feltā¦ uncomfortable. But that does make it quite clunky (e.g. thereās a different derived type for different rank return data)
For example, the function that might contain an error could look like this:
function squareroot(x)
type(Result0D) :: squareroot
real :: x
if (x < 0.0) then
call squareroot%addError(ErrorInstance(message="x cannot be less than 0"))
end if
call squareroot%setData(sqrt(x))
end function
And then the code this is called from could look like:
type(ErrorHandler) :: EH
type(Result0D) :: rslt
rslt = squareroot(-1.0)
! Only triggers if rslt contains an error
call EH%trigger(.errors. rslt)
Might have the syntax slightly wrong as Iām on my mobile, but the principle is there.
Internally, the ErrorHandler
just prints out the error and triggers an error stop
when it is triggered - so not very elegant.
@Arjen, youāre conflating different aspects: I suggest you consider the following:
- whatever āparticular type of functionsā you may have in mind, if your intent is to package in a FOSS public-domain library, then if you have a way of knowing when the function result can be outside the range of expected values such as with function input outside of valid domains, you would do well to
ERROR STOP
explicitly, - As to intrinsic functions in Fortran, what is suggested in point 1 is effectively what they do as well except that the whole ecosystem currently around the language standard and processor-dependent behavior and what-not has left it somewhat vague, meaning it all departs from KISS from an unsuspecting Fortran practitioner point-of-view. A better way to look at your latest example with
sqrt
andlog
is instead this scenario:
use :: ieee_exceptions, only : ieee_set_halting_mode, IEEE_INVALID
real :: x
call ieee_set_halting_mode( IEEE_INVALID, halting=.true. )
call random_number( x )
x = sqrt( x - 1.0 )
print *, "x = ", x
end
C:\Temp>gfortran p.f90 -o p.exe
C:\Temp>p.exe
Program received signal SIGFPE: Floating-point exception - erroneous arithmetic operation.
Backtrace for this error:
#0 0x434dab
#1 0x42a984
#2 0x40cbe1
#3 0xe6b27ff7
#4 0xe7f520ce
#5 0xe7f01453
#6 0xe7f50bfd
#7 0x4015a2
#8 0x40166d
#9 0x4013c0
#10 0x4014f5
#11 0xe7ce7033
#12 0xe7f02650
#13 0xffffffff
C:\Temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.-out:p.exe
-subsystem:console
p.objC:\Temp>p.exe
forrtl: error (65): floating invalid
Image PC Routine Line Source
p.exe 00007FF6AB6E10AF Unknown Unknown Unknown
p.exe 00007FF6AB7316BE Unknown Unknown Unknown
p.exe 00007FF6AB731A40 Unknown Unknown Unknown
KERNEL32.DLL 00007FFDE7CE7034 Unknown Unknown Unknown
ntdll.dll 00007FFDE7F02651 Unknown Unknown Unknown
So if youāre authoring a function FOO
similar to SQRT
and LOG
, you will be KISSing your users by employing ERROR STOP
the minute you realize something is out of whack (such as x < 0.0 ) rather than letting other events and actions trigger the same action way downstream of the source where the root cause could have been identified.
As much as I agree with your statement in a previous post that one should not return a NaN on error, I donāt find using error stop
in a library a good idea.
Whether on is writing a FOSS library or a company/group internal library that is used in more than one project it is key to appreciate that we, as the library author, donāt know how others intend to use the library. There are multiple scenarios where an error stop
inside a library procedure would not be acceptable for me as a library user:
- After the failed library call I might wish to output an error message to a log file, write some buffered results to a result file and gracefully close all resources
- I might wish take action on the error and continue with execution. Many Fortran based applications will stop and ask the user to take action when a failure has occurred, but this cannot be the assumed behaviour of a library. An optimization algorithm with support for handling failed evaluations is one example of this.
- If I want to integrate the library into another application and
error stop
would not often not be acceptable. For example if the code is run with a Python wrapper theerror stop
would take down the whole Python process.
For libraries in particular I think itās very important that
- Errors are handled gracefully (no
error stop
-s) - Specific classes of errors are possible to identify programmatically so that the user may choose to recover from them
- Error information is transferred back to the caller and not printed to stdout/stderr
Following these guidelines will make the library much easier to integrate into various applications which, of course, is our goal when writing a library.
Agreed. There are many cases in which a single error does not make much (if any) difference on final results. Examples include image processing (you always find some bad pixels or cosmic rays on the CCD chip but it has no meaning for the 99.99% of the results calculated on, say, 4k x 4k chip or, even less so, 512M CCD mosaic), probably also (though I am no expert) in weather modelling etc. Forcing error stop
to a complicated process running for hours is definitely not a good idea. And even if the error cannot be just ignored, it may well be much easier and less resource consuming to do a simple check for error (examining a single integer variable) than to check validity of every point of data, which may involve much more calculations.
The behavior that failure terminates the program unless an error code is requested is common in Fortran. Statements like allocate
or open
behave like that (optional IOSTAT
or STAT
argument).
That is why I suggest to either error stop
OR state whether a return value that something went wrong. The library user needs to decide whether a failure is acceptable, not the library developer. Unfortunately, this means that functional programming is impossible because a function cannot return two values and Fortran has no mechanism to catch errors.
Agreed. This is very unfortunate. Not only for the desire of programming in a āfunctionalā style, but for the use of pure functions in general. With the current set of language features pure functions can realistically only be infallible.
What Fortran really would benefit from is support for rich enumerations or tagged unions. Then one could write functions that either return a value (with a specified type) or an error (with another specified type). This should preferably be combined with good generics support to avoid boilerplate code.
The best workaround I can think of today is to define a type, e.g.
type :: result_int_t
character(len=:), allocatable :: error
integer, allocatable :: value
end type
and then only allocate one of the members depending whether the function failed or succeeded, for example:
type(result_int_t) pure function foo(i) result(res)
integer, intent(in) :: i
if (i > 42) then
res%error = 'For some reason this is not ok'
else
res%value = i + 2
end if
end function
I think this is similar to what @samharrison7 proposed in a previous post.
The context of my comments is the situation by OP with a FUNCTION
that can encounter an error (OP then used sqrt
and log
as illustrative examples).
With current state of Fortran, one can resort to use SUBROUTINE
subprograms under the circumstances which was next point in my suggestion, or employ ERROR STOP
in the FUNCTION
.
There are decided benefits with the use of FUNCTION
s in expressions and there is the whole paradigm of functional programming predicated on particular values with the approach. Then if the exceptions are truly as they should be i.e., exceptions, then proceeding with the use of FUNCTION
s with ERROR STOP
will be the lesser of the āevilā. NaNs will soon lead to an error stop anyway but after if it has infected most or all of the system but with little idea as to the source of the exception.
Agree. If the error scenario is really exceptional then a error stop
might be appropriate. Preferably with proper documentation along with the relevant procedures.
Given its name It is actually quite ironic how often exceptions are thrown around in codebases written in certain mainstream languages.
Thatās very unfortunate as I agree that this is the best practice, and as some of the other posts have noted, it can be combined with error stop
in the case that stat
and/or errmsg
are not given. Given that it is not fixed now, it will likely take a number of years before a compatible version of GFortran is provided generally through package managers.
Modern Fortran needs exception handling. Fortran is way behind on this, as in many other things that modern programmers expect and depend on from other languages.
Being way behind can also be an advantage to ādo things rightā when the time comes. As an analogy my home village in rural Slovenia has optic fiber (because it arrived very late), while cities in Germany are stuck with old DSL connections.
Hereās a C++ talk on De-fragmenting C++: Making Exceptions and RTTI More Affordable and Usable - Herb Sutter CppCon 2019 - YouTube, which shows the opinions on exceptions are fragmented. Iāve taken a snapshot of one of the slides:
I also used to be of the opinion that what Fortran really was lacking was exceptions. However lately I have begun doubting that this is the best way forward. The downsides with exceptions are multiple and significant, among others:
- Code flow quickly become very convoluted when you want to recover from exceptions.
- When reading code it is difficult to determine which procedures might throw an exception and which does not. As a result it is for example easy to either program too defensively or forget to handle exceptions in critical parts of the code.
Seeing how Rust solves this has led me to believe there might be a better way forward for Fortran. Interestingly Rust error handling is very similar to Fortran in that fallible functions require explicit handling of the potential error.
The difference is in that Rust has language features and a standardized strategy for propagating errors throughout the code. This essentially boils down to support for generics and functional style enums/tagged unions which makes it possible for a function to either return a value or an error in the Result
enum. In addition thereās the question mark operator which is basically just syntactical sugar that makes returning early in the event of an error easy.
Take the function in my previous example as a starting point. Use of this function could look something like this:
a = foo(1)
if (allocated(a%error)) return
b = foo(a%value + 1)
if (allocated(b%error)) return
c = foo(b%value + 1)
if (allocated(c%error)) return
write(*,*) 'Answer is ', c%value
The Rust way would conceptually look something like this:
a = foo(1)?
b = foo(a + 1)?
c = foo(b + 1)?
write(*,*) 'Answer is ', c
Or even more compact:
write(*,*) 'Answer is ', foo(foo(foo(1)? + 1)? + 1)?
I find both reading and writing this sort of fallible code very pleasant: When writing, it is near impossible to forget to handle a potential failure. When reading, it is obvious what code might fail and which actions are taken in case it fails.
Iām not saying that Fortran should just do exactly like Rust, but seeing that there exists a good solution that conceptually is the same as we do today makes me believe that there are alternatives to exceptions. I also believe a solution along these lines would fit much better into an existing fortran codebase where parts of the old code probably would use an integer or logical argument to check if calls have failed.
Exceptions has one significant advantage though: Especially for the successful code path they are probably the most performant way of implementing error handling.
@Arjen and anyone else interested in this, shown below is a keep-it-simple strategy recommended based on current Fortran standard and all that it entails i.e., no built-in exception handling, etcā¦ The basic approach is as I suggested upthread .
Click to expand!
module kiss_m
abstract interface
pure subroutine Ikiss_error_handler( stat )
integer, intent(in) :: stat
end subroutine
end interface
procedure(Ikiss_error_handler), pointer :: kiss_error_handler => default_handler
contains
pure subroutine default_handler( stat )
integer, intent(in) :: stat !<-- enumerator_type in >=Fortran 2023
! Handle an established list of exceptions as identified for this library
select case ( stat )
case ( 1 )
error stop "kiss_func: Invalid input argument exception"
!case ( .. ) elided are other cases
case default
error stop "kiss_func: Unsupported operation exception"
end select
end subroutine
subroutine set_handler( proc_handler )
procedure(Ikiss_error_handler) :: proc_handler
! elided are any checks for valid handler
kiss_error_handler => proc_handler
end subroutine
elemental function kiss_func( x ) result( r )
integer, intent(in) :: x
integer :: r
integer :: stat !<-- enumerator_type in >=Fortran 2023
if ( x < 0 ) then
! An exception situation
stat = 1 !<-- enumerator assignment in >=Fortran 2023
call kiss_error_handler( stat )
end if
r = x + 1
return
end function
elemental subroutine kiss_sub( x, y, stat, errmsg )
integer, intent(in) :: x
integer, intent(inout) :: y
integer, intent(out) :: stat
character(len=*), intent(inout) :: errmsg
stat = 0
! Code instructions
y = x**2 + 2*x - 21
! Some error situation
if ( y == 42 ) then
stat = 1
errmsg = "Uh oh, the world must end, you've arrived at the answer to everything!"
return
end if
return
end subroutine
end module
use kiss_m
integer :: a, b, irc
character(len=256) :: msg
a = 7
call kiss_sub( a, b, irc, msg )
if ( irc /= 0 ) print *, trim(msg)
print *, kiss_func(-1)
end
C:\Temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.-out:p.exe
-subsystem:console
p.objC:\Temp>p.exe
Uh oh, the world must end, youāve arrived at the answer to everything!
kiss_func: Invalid input argument exception
A couple of comments with above:
- With programs other than a Fortran processor consuming such a library, one ācheatsā by providing a custom handler that can possibly be unpure but whose interface in the Fortran side of things gets attributed as pure - a compromise given the state of affairs.
- An issue can be where a consumer of such library
SUBROUTINE
APIs fails to check and respond appropriately to thestat
return code. Given the Fortran standard intrinsics, it will not be too foreign to leave this as āuser errorā.
Yes, when I say Fortran needs exception handling, I donāt mean to imply that it should have exactly what C++ or Python or whatever has. I just mean the language needs some standardized way to handle exceptions and errors. What we have now is basically nothing, so every program and library has to roll their own (or just error stop LOL
when there is a problem). It makes building an ecosystem very difficult.
Some things can be handled in libraries, but error exceptions should be in the language.
To reiterate, ERROR STOP
is only suggested for FUNCTION
subprograms.
Fortran has already done half a step into exception handling in the C++/Python style when it comes to floating point exceptions:
program exception
use IEEE_arithmetic
implicit none
real :: small = 1.0e-56
logical :: flag
type(IEEE_status_type) :: v
flag = .false.
call IEEE_set_flag(IEEE_all,.false.)
print*, flag
print*, 0.0/small
call IEEE_get_flag(IEEE_invalid,flag)
print*, flag
end program exception
Theoretically, one can use this functionality to implement exception handling in a broader scope. Every time something goes wrong, one sets the IEEE_invalid
flag. This is more or less equivalent to using a global variable, just that the compiler takes care.
It is also interesting to see that the topic is discussed for at least 25 years:
Thanks for the references. The 2nd link did not work for me, but Error handling in Fortran 2003 did.