Idioms for exception handling

The presentation on Modernizing Legacy Fortran codes by R. Bader linked in a recent post, suggests the following idiom for dealing with exceptions:

integer :: stat

comp: block
   real :: x
   x = …
   call gam(x, stat)
   if (stat /= 0) exit comp
   ! :
end block comp

select case (stat)
case(0)
   stop 0
default
   write(*,*) 'error:', stat
   error stop 1
end select

The “exception handling” occurs after the named block (here rather unimaginative, as the author remarked himself).

The Odin programming language also uses this idiom and does not to include an exception mechanism. In the Q&A section they state:

Why does Odin not have exceptions?

Coupling exceptions to a control structure, as in the try-catch-finally idiom, complicates the understanding of the program.

Odin uses plain error handling through the use of multiple return values. It is clear which procedure the error value is from compared to a try-catch approach which is akin to the COMEFROM statement.

Please see gingerBill’s article for more information: Exceptions — And Why Odin Will Never Have Them.

The linked article by gingerBill, gives the following example of exception handling in Odin:

Error :: union {
	ValueError,
	BarError,
	BazError,
	PlopError,
}

foo :: proc() -> (Value_Type, Error) { ... }

x, err := foo();
switch e in err {
case ValueError:
	// Handle error
case BarError:
	// Handle error
case BazError, PlopError:
	// Handle errors
}

I just found this similarity interesting, and wanted to save the links for future reference. In case you are interested in exception handling in Fortran, there are several past related threads:

8 Likes

Now that F2023 has enumeration types (see the presentation by J. Reid (PDF, 313 KB)), perhaps this becomes a more widespread way of error handling once compilers will support the new language facility:

enumeration type :: error
   enumerator :: Success, ValueError, BarError, BazError, PlopError, SevereError
end type

type(error) stat
real :: x

x = foo(err=stat)

select case(stat)
case(ValueError)
   ! handle error
case(BarError)
   ! handle error
case(BazError,PlopError)
   ! handle error
end select

contains

   impure function foo(err)
      type(error), intent(out) :: err
      real :: foo
      ! ... 
   end function

I’m not sure how the next and previous intrinsics could be used? The enumeration type supports comparison operators, so these can also be used to define error ranges:

if (stat /= Success) then
   ! some error occured
end if

if (stat >= SevereError) then
   ! a bad error you really should respond to
end if

I suppose it makes sense to always use error(1) as the success flag. According to the rules laid out here (PDF, 276 KB), the enumeration type can also be used as follows:

nerrors = huge(stat)
select case(stat)
case(error(2):error(nerrors))
   print *, "Panic!"
case(error(1))
   print *, "Everything okay"
end select
4 Likes

A little off topic here but looking at Reid’s 2023 presentation can someone explain why Fortran needs basically three ways to do enumerations. Why couldn’t the standards folks just have removed the requirement for BIND(C) except in the cases were you are actually doing C-Interop, add the ability to name the enum (I believe that was in the original enum proposal because Cray implemented it that way around 2002, 2003 time frame and might still have it in their compilers as an extension), and just extend the current capability to do all the other things the new enumerator does. Like class(*) and type(*), why is the standards committee so keen on basically adding a new feature that could have easily been obtained by extending an existing one.