Responding to a STOP declaration

I have a series of STOP declarations in one program, that is called by another.

I’d prefer the called program to respond to the STOP by returning to the calling program; potentially with an error code.

I believe there is a @STOP procedure I can build as a response, but this won’t return to the calling program (?).

Is there anything simple I could do?

Yeah, I started doing just that and thought: no.

Too much work.

Thank you though; stops me pondering on that one. :slight_smile:

What exactly do you mean by “calling program”? Is this a case of a separate executable that is invoked somehow, such as EXECUTE_COMMAND_LINE? If so, then the standard encourages processors to return a numeric stop code as the “exit status”. If you’re using EXECUTE_COMMAND_LINE, you can detect this.

Exception handling is confusing and sometimes even more frustrating when it “does exist.” I would prefer my machine to just shut down if a running Fortran program encounters any error. This way, power will be saved and I can rest easy knowing that I’m doing my part towards a greener planet.

1 Like

I have two Fortran files; dummymain.f90 and stelcor.f90

I compile these into a single executable, but dummymain calls stelcor through a call statement.

The STOP declaration is within the code itself; it is not being generated by an error. Basically, the system runs out of data and the code spots this then ends the execution through the STOP command. This is within stelcor.

The problem is that stelcor is a whole load of functions and procedures and passing up an error value would be very difficult, since there is often a chain of called subroutines between the top of stelcor and the place where the file’s data becomes useless.

It’s at a point that my code should not run up to but I thought a nice catch and a clean return to dummymain would be nicer than the code just stopping.

Is your primary goal to have the code always exit through the program in dummymain.f90, or somehow indicate that you’ve reached an alternate STOP condition in stelcor.f90, or actually write out which STOP condition you’ve reached in stelcor.f90? It sounds like you don’t actually have an error, but rather just want program execution to stop through some alternative route rather than immediately at the first STOP encountered.

No, there is no error per se; the code exhausts the data it has available for it. The issue is that this happens deep down within the stelcor code; so the STOP happens many subroutine calls in and I would need to cascade all the way back up through the code, in the right places, to get an error code back to the root subroutine and back out to dummymain.

The original code obviously had these stops in place to trap expected issues. There is also a variable ierror that appears in places, that I can see was going to be the start of some form of return flag.

I initially just wanted dummymain to receive back control, recognise that a STOP had been declared and close appropriately. I envisaged using the ierror variable to trigger this, but getting this to trigger all the way back up through stelcor is likely to be a nightmare; and not that important!

It was a ‘final’ tweak of fun, if I can put it that way.

You could do something gross like this:

module mymod
implicit none
private

    public :: work_wrapper

    contains

        recursive subroutine work_wrapper(args, msg)
            integer, intent(in) :: args
            character(len=*), intent(in), optional :: msg
            write(*,*) 'WORK_WRAPPER -- inside work_wrapper, doing work like CALL stelcor'
            call stelcor(args)
            write(*,*) 'WORK_WRAPPER -- if we get here, exiting through work_wrapper'
            error stop 'WORK_WRAPPER -- stelcor completed without reaching a STOP'
            entry alternate_end(msg)
            if (present(msg)) write(*,*) 'msg: ',msg
            write(*,*) 'WORK_WRAPPER -- we want to actually stop here'
            STOP
        end subroutine work_wrapper

        subroutine stelcor(args)
            integer, intent(in) :: args
            write(*,*) 'STELCOR -- in stelcor, let''s do whatever...'
            if (args == 1) then !! any various STOP condition
                write(*,*) 'STELCOR -- stelcor used to STOP here'
                call alternate_end(msg='STELCOR is the captain now')
            end if
            write(*,*) 'STELCOR -- stelcor finished normally, returning to caller'
        end subroutine stelcor

end module mymod

program main
use, non_intrinsic :: mymod, only: work_wrapper
implicit none

    call work_wrapper(1)

end program main

We can’t have an entry in the main program, but you could wrap everything that happens in program main inside a single routine, call it work_wrapper. Then, you just call that, and inside of work_wrapper, you may have an alternate entry, which is called everywhere in stelcor that you currently have STOP. Just make sure the alternate entry (in this case it is called alternate_end) actually leads to a STOP to halt program execution.

You can even put an optional message (msg) as an argument for your alternate_end, so you can print out which condition got you there.

1 Like

@tyranids This should work, but keeping in mind that the whole calling stack remains instead of being purged. Not a problem if after the return one just wants to perform some limited post-processing before quitting, but it can be if the objective is to continue with another big processing (e.g. another call to stelcor() or whatever). Also, work_wrapper() should be declared as recursive (unless a fully compliant F2018 compiler is used, as all routines are now recursive by default I think).

Good catch. I tried it out with gfortran and LFortran, both of which worked without issue. LFortran only yelled at me for style, because apparently I should not be using .eq. when == is available.

Thanks for this.
I have already undertaken the cascading error flag approach that runs back up through the function calls, back to dummymain. Though this, at first, looked horrendous, it wasn’t that bad.

I will keep your solution at hand. I might prefer this option when I have the time to process it fully.

I’m glad to hear it. The error propagated up is definitely a better design, although it can be a hassle as you’ve found to add to a project after the fact.

An alternative to propagating up an error code through the routine arguments can be to put all the routines in a module (if not already the case), and declare a module variable that contain the status of the computations. Still, all the STOP have to be converted into STAT=-1 ; RETURN, and after each call that can change STAT a test IF (STAT /= 0) RETURN has to be inserted, but at least one doesn’t have to add an argument to all the subroutines. This is not thread-safe, though.

That is, in fact, what I have done! :slight_smile:

Here is another general approach to this problem. You can add an ISTAT optional argument to your argument lists. Each routine must check for present(ISTAT), and set it accordingly upon return. If the argument is not present, then it does whatever error handling and reporting is appropriate and exectutes a STOP or an ERROR STOP.

Your existing code without the argument can remain unchanged, and errors that are generated will then be treated as before, with the program halting when the error occurs. But if you want the routine to return instead, then you just add the ISTAT argument as appropriate.

Optional arguments require an explicit interface, so that may also require some program restructuring, such as moving routines into modules and adding USE statements.

1 Like

You just want a special case where you return to the top? One way not mentioned is to make the main entry point a recursive subroutine. Unfortunately, the PROGRAM directive is not callable recursively itself except as a call to start a new process, but it is not too too ugly to just make an immediate call to a subroutine that acts as the real program top. It did not seem mentioned, nor did alternate returns, which used to be used in clever ways to jump back up through stacks (but are now removed or deprecated from the Fortran standard) and pointers to functions; but corrupting you with one code twist at a time is probably sufficient.

program recursive_main_jsu
  implicit none
  call top()
contains
  recursive subroutine top(icode)
  integer,optional,intent(in) :: icode
  integer, save :: callcount=0
  callcount=callcount+1
  if(callcount == 1)then
     write(*,*)'hello!. First time here?',callcount
     call a()
  else
     write(*,*)'welcome back,callcount=',callcount
     if(present(icode))then
        write(*,*)'stopping with code',icode
        stop icode
     else
        write(*,*)'it was nice visiting, returning to call point after recovering'
     endif
  endif
  end subroutine top
  subroutine a()
          write(*,*) 'start a'
          call b()
          write(*,*) 'end a'
  end subroutine a
  subroutine b()
          write(*,*) 'start b'
          call c()
          write(*,*) 'end b'
  end subroutine b
  subroutine c()
          write(*,*) 'start c'
          write(*,*) 'recoverable error, go to top and fix things'
          call top()
          write(*,*) 'back in c, now go to top and stop with error'
          call top(10)
          write(*,*) 'end  c'
  end subroutine c
end program recursive_main_jsu