Error handling approaches

For a subroutine

subroutine foo(xmat,yvec,iuse)
real, intent(in) :: xmat(:,:) ! (n,ncol)
real, intent(in) :: yvec(:)    ! (n)
integer, intent(in), optional :: iuse(:)
end subroutine foo

I need all the elements of iuse(:), which will be used as a vector subscript for xmat and yvec, to be between 1 and size(yvec), or there will be an out-of-bounds error. How you do decide which way to handle this:

(1) Do nothing. Let the program crash for invalid iuse.

(2) Check that iuse is valid upon entering foo and
(a) print an error message and STOP
(b) print an error message and RETURN
(c) set an error flag argument ierr and RETURN
(d) do either (a) or (c) depending on whether optional error flag ierr is passed.

(3) Check the input and fix it if invalid. Define an array iuse_(:) = pack(iuse,iuse>0 .and. iuse <= n) and use iuse_ as the vector subscript.

Since it’s an individual project I will probably do 2(a), which forces the calling code to be corrected.

I’m pretty new to Fortran so take my advice with a grain of salt, but I’m a fan of a hybrid approach between 2c and 2a… have an OPTIONAL error flag argument. If it’s provided, set it when an error ocurrs. If the flag argument is not provided just do stop with an error message.

I like this approach because the caller can decide if they want to handle errors or if they want them to be fatal.

Edit: I just realized that’s exactly what you’re saying in 2d… So I vote for 2d!

1 Like

I lean towards 2c, but I would say 2d is pretty typical and acceptable, provided you use error stop instead of stop.

@pmk, alternate return scares me. But I have seen it suggested that it could be used as a poor man’s emulation of exception handling, which intrigues me.

1 Like

1 for high performance applications. In development I enable the run-time bounds checking and let the program stop itself on bad input.

2a for other applications, but with error stop.

2d for libraries. The user should decide whether to stop or not.

3 Likes

I’m a “culprit” when it comes to such suggestions, see an example here!

(4) Consider a parameterized derived type “container” toward matrices and associated vectors, that provides a surefire and efficient method for bounds matching. Intel oneAPI IFORT is now quite functional here, so appears to be NAG Fortran 7.0.

..
type :: mat_t(n,m)  ! may be just 'n' for square matrices
   integer, len :: n, m
   real :: xmat(n,m)
   real :: yvec(n)
   integer :: iuse(n)
..
contains
   subroutine foo( this, luse )
      type(mat_t(n=*,m=*)), intent(inout) :: this
      logical, intent(in), optional :: luse
      ! No bounds checking necessary here
      if ( present(luse) ) then
         if ( luse ) then ! use this%iuse in the instructions
..

My habits were formed before Fortran introduced ERROR STOP, but reading What is the difference between STOP and ERROR STOP?, I see it’s what I should be using to handle errors.

For functions I think the two main approaches are ERROR STOP or returning an obviously bad RESULT, that one hopes the calling program will catch, for example

pure function correl(x,y) result(corr)
! use ERROR STOP
real, intent(in) :: x(:),y(:)
real             :: corr
if (size(x) < 2) then
   error stop "in correl, need size(x) > 1"
else if (size(x) /= size(y)) then
   error stop "in correl, need size(x) == size(y)"
end if
! calculate corr
end function correl
!
function correl_old(x,y) result(corr)
! use STOP if compiler does not support error stop
real, intent(in) :: x(:),y(:)
real             :: corr
if (size(x) < 2) then
   print*,"in correl, need size(x) > 1"
   stop
else if (size(x) /= size(y)) then
   print*,"in correl, need size(x) == size(y)"
   stop
end if
! calculate corr
end function correl_old
!
pure function correl_f95(x,y) result(corr)
! return clearly bad result for invalid input
real, intent(in) :: x(:),y(:)
real             :: corr
if (size(x) < 2) then
   corr = -2.0
   return
else if (size(x) /= size(y)) then
   corr = -3.0
   return
end if
! calculate corr
end function correl_f95

We missed the chance to have STOP and STROP (to “throw a strop” is a Britishism).

1 Like

Definitely 1 for high performance applications, if the subroutine is called many times. If it is a high level subroutine, then you can put the check there. Always enable bounds checking in Debug mode and always check your final application in Debug mode on actual input (test) data to ensure everything works. Then run in Release mode for production runs.

I generally do not like to use pre-processing, but using ASSERT macros (enabled in Debug mode, but no-op in Release mode) can also be used for this purpose.

2 Likes