Testing programs that exits with error codes

Hi all! While adding tests to my codes (I’m using test-drive and fpm test) I want to test that a subroutine makes the code exit if some condition happens. Something like:

subroutine test_this(x)
      real, intent(in) :: x

     if (x > 5) then
         call exit(1)
     end if
end subroutine

Of course, having this exit will exit the test procedure making it seem like a failed test. Is there any way to test this kind of exits? My projects are still relatively small so changing the testing framework wouldn’t be a pain for me either if I need to change it.

Thanks!

I do not know how this can be done in this test framework, but for my ftnunit system (see http://flibs.sf.net) I use a batch file/shell script to run the test program as often as necessary. That is meant to catch unexpected crashes and the like.

I use a shell script like the following one:

#!/bin/sh

TESTS="test1 test2 test3"
NTEST=`echo ${TESTS} | wc -w`
NFAIL=0

for TEST in ${TESTS}; do
    ./${TEST}
    if [ $? -ne 0 ]; then
        NFAIL=`expr ${NFAIL} + 1`
        printf "++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++\n"
        printf "TEST ${TEST} FAILED!\n"
        printf "++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++\n"
    fi
done

printf "++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++\n"

if [ ${NFAIL} -eq 0 ]; then
    printf "ALL %s TEST PROGRAMS FINISHED SUCCESSFULLY!\n" ${NTEST}
else
    printf "%s OF %s TEST PROGRAMS FAILED!\n" ${NFAIL} ${NTEST}
fi 

The test programs test1, test2, test3 have to be in the same directory.

If you turn off autodiscovery of the programs and then make a fortran program that calls the program and checks the return status you can write all your test programs to return an exitstatus and have them all end with a STOP. That makes making lots of little tests easy as well as testing for tests that stop the programs.

You can even do it in a single program that calls itself.

recursive
program demo_get_command_argument
implicit none
character(len=*),parameter :: gen='(*(g0))'
integer                    :: exitstat,cmdstat
character(len=256)         :: cmdmsg
if( command_argument_count() == 0 )then
   write(*,gen)'program name ',arg(0)
   write(*,gen)repeat('=',80)
   call execute_command_line(arg(0)//' case1',wait=.true.,exitstat=exitstat,cmdstat=cmdstat,cmdmsg=cmdmsg)
   call expected('case1',10)
   call execute_command_line(arg(0)//' case3',wait=.true.,exitstat=exitstat,cmdstat=cmdstat,cmdmsg=cmdmsg)
   call expected('case3',0)
   call execute_command_line(arg(0)//' case2',wait=.true.,exitstat=exitstat,cmdstat=cmdstat,cmdmsg=cmdmsg)
   call expected('case2',1)
else
   select case(arg(1))
   case('case1'); call boom10()
   case('case2'); call boom0()
   case('case3'); call boom1()
   case default
      write(*,*)'<ERROR>unknown case ',arg(1)
   end select
endif
contains
subroutine expected(label,expect)
integer,intent(in)          :: expect
character(len=*),intent(in) :: label
   write(*,gen)arg(0),' CASE ',label,' ',merge('PASSED','FAILED',expect==exitstat),'; EXPECTED ',expect,' GOT ',exitstat
   write(*,gen)repeat('=',80)
end subroutine expected

subroutine boom10()
   ! procedure that stops program
   stop 10
end subroutine boom10

subroutine boom0()
   ! procedure that stops program
   stop 0
end subroutine boom0

subroutine boom1()
   ! procedure that stops program
   error stop 1
end subroutine boom1

function arg(i)
character(len=:),allocatable :: arg
integer,intent(in) :: i
integer            :: argument_length
   call get_command_argument(number=i,length=argument_length)
   if(allocated(arg))deallocate(arg)
   allocate(character(len=argument_length) :: arg)
   call get_command_argument(i, arg)
end function arg

end program demo_get_command_argument

This assumes your system returns exit status. I do not know of one that does not anymore; but there might still be one.

There are other ways to trap signals in Fortran but they all require calling C or using something non-standard so calling execute_command_line is the “Fortranik” method.

So this is a “pure Fortran” approach. The Fortran wiki has a list of test frames, some of which support testing failing executables in other ways (I use M_framework for obvious reasons :>)

1 Like

I think it would be a nice enhancement to fpm to allow specifying an expected exit status for test programs in the fpm.toml file; and when present compare that value and write a simple passed/failed message similiar to the example program above and a tally of how many matched. Albeit it would be
a simple one it would give fpm a built-in testing framework without requiring any external modules or packages. If multiple executions of the test program(s) were allowed with command options as well or a way to pass environment variables just a few lines of code added to fpm would be nice. I would assume if the exit status matched the expected value the tests would continue on.

A switch to allow execution to continue even if one program failed with be useful for examples and tests regardless.

1 Like

Nice idea @urbanjost! I didn’t think about using system calls and keeping the exit stat, that’s a quick and easy fix. I still think that it will be a nice addition to either fpm or a test suite to have this kind of functionality

In standard fortran, one would now use something like error stop 1 to generate the nonzero return code. I think the nonstandard exit() subroutine allows variables as the argument, while error stop requires a constant expression, but the return codes are generated the same way in both cases.

1 Like

In f2018 error stop doesn’t need a constant expression, but some compilers have not yet implemented that change from f2008.

1 Like

There are still some gotchas as there are a lot of mentions in the standard of
aspects of program termination (both normal and error) being
processor dependent.

The range of values returned is processor-dependent, for example.

For STOP the range is typically the lower eight bits, or from 0 to 255 on GNU Linux
and Unix. That is, it looks like any default integer value can be used, but for the
number returned to be the number specified only a limited range of values is available.

Empirically testing with various processors ERROR STOP it is not always the same range as for STOP which I found surprising. Reading the standard
it is easy to see that one might interpret ERROR STOP as never returning 0,
and some provide a backtrace as part of error termination, but not
always if the value is zero.

but sometimes 0 and N*256 do return zero and sometimes they do not.

I think that STOP and ERROR STOP should return the same number to the
system given the same input number and getting a backtrace is useful.
Given that it is not required though, I prefer having a separate procedure
for producing a backtrace – but not all compilers supply one, let alone
there being a standard way so it is better than nothing.

program demo_error_stop
implicit none
character(len=*),parameter   :: gen='(*(g0))'
integer                      :: exitstat,cmdstat
character(len=256)           :: cmdmsg
integer                      :: i, j, iexit
character(len=:),allocatable :: line
if( command_argument_count() == 0 )then
   do i=0,256
      line=repeat(' ',10)
      write(line,'(g0)')i
      call execute_command_line(arg(0)//' '//trim(line),wait=.true.,exitstat=exitstat,cmdstat=cmdstat,cmdmsg=cmdmsg)
      if(exitstat.ne.i) write(*,*)i,exitstat,i==exitstat
   enddo
else
   line=arg(1)
   read(line,*)iexit
   error stop iexit,quiet=.false.
   !stop iexit,quiet=.false.
endif
contains
function arg(i)
character(len=:),allocatable :: arg
integer,intent(in) :: i
integer            :: argument_length
   call get_command_argument(number=i,length=argument_length)
   if(allocated(arg))deallocate(arg)
   allocate(character(len=argument_length) :: arg)
   call get_command_argument(i, arg)
end function arg
end program demo_error_stop

For ifx(1),
zero does not return zero, and I have no idea why 127 returns
126. And if zero does not return zero (which you can argue is OK
depending on how you interpret the standard) then it is odd that
256 does. What happens is processor-dependent but STOP does not
treat 127 differently, and STOP and ERROR STOP not doing the same
thing with zero is confusing, but it would be nice to get a
clarification on what the (preferred?) behavior should be for
zero.

ifx xx.f90 && ./a.out
 0    128  F
 127  126  F
 256  0    F

For gfortran the lower eight bits are always returned, more like
C on GNU and Unix platforms that I have access to

 gfortran xx.f90 && ./a.out
 ... deleted the backtraces
 256           0 F

Should ERROR STOP ever return a zero? These are the pertinent sections I could
find …

      1       5.3.7    Termination of execution
      2       Termination of execution of a program is either normal termination or error termination. Normal termination
      3       occurs only when all images initiate normal termination and occurs in three steps: initiation, synchronization,
      4       and completion. In this case, all images synchronize execution at the second step so that no image starts the
      5       completion step until all images have finished the initiation step. Error termination occurs when any image
      6       initiates error termination. Once error termination has been initiated on an image, error termination is initiated
      7       on all images that have not already initiated error termination. Termination of execution of the program occurs
      8       when all images have terminated execution or failed.
      9       Normal termination of execution of an image is initiated when a STOP statement or end-program-stmt is executed.
     10       Normal termination of execution of an image can also be initiated during execution of a procedure defined by a
     11       companion processor (ISO/IEC 9899:2018, 5.1.2.2.3 and 7.22.4.4). If normal termination of execution is initiated
     12       within a Fortran program unit and the program incorporates procedures defined by a companion processor, the
     13       process of execution termination shall include the effect of executing the C exit() function (ISO/IEC 9899:2018,
     14       7.22.4.4) during the completion step.
     15       Error termination of execution of an image is initiated if an ERROR STOP statement is executed or as specified
     16       elsewhere in this document. When error termination on an image has been initiated, the processor should initiate
     17       error termination on other images as quickly as possible.
     18       If the processor supports the concept of a process exit status, it is recommended that error termination initiated
     19       other than by an ERROR STOP statement supplies a processor-dependent nonzero value as the process exit
     20       status.
              NOTE1
              As well as in the circumstances specified in this document, error termination might be initiated by means other
              than Fortran.
              NOTE2
              If an image has initiated normal termination, its data remain available for possible reference or definition by
              other images that are still executing.

      14        11.4        STOP and ERROR STOP statements
      15        R1162 stop-stmt                             is   STOP[stop-code ] [ , QUIET = scalar-logical-expr]
      16        R1163 error-stop-stmt                       is   ERROR STOP [stop-code ] [ , QUIET = scalar-logical-expr]
      17        R1164 stop-code                             is   scalar-default-char-expr
      18                                                    or scalar-int-expr
      19        C1176 (R1164) The scalar-int-expr shall be of default kind.
      20        Execution of a STOP statement initiates normal termination of execution. Execution of an ERROR STOP
      21        statement initiates error termination of execution.
      22        When an image is terminated by a STOP or ERROR STOP statement, its stop code, if any, is made available
      23        in a processor-dependent manner. If the stop-code is an integer, it is recommended that the value be used as
      24        the process exit status, if the processor supports that concept. If the stop-code in a STOP statement is of type
      25        character or does not appear, or if an end-program-stmt is executed, it is recommended that the value zero be
      26        supplied as the process exit status, if the processor supports that concept. If the stop-code in an ERROR STOP
      27        statement is of type character or does not appear, it is recommended that a processor-dependent nonzero value
      28        be supplied as the process exit status, if the processor supports that concept.
      29        If QUIET= is omitted or the scalar-logical-expr has the value false:
      30           *  if any exception (17) is signaling on that image, the processor shall issue a warning indicating which
      31              exceptions are signaling, and this warning shall be on the unit identified by the named constant ERROR_-
      32              UNIT from the intrinsic module ISO_FORTRAN_ENV (16.10.2.9);
      33           *  if a stop code is spefied, it is recommended that it be made available by formatted output to the same
      34              unit.
      35        If QUIET= appears and the scalar-logical-expr has the value true, no output of signaling exceptions or stop code
      36        shall be produced.
                NOTE1
                 When normal termination occurs on more than one image, it is expected that a processor-dependent summary
                 of any stop codes and signaling exceptions will be made available.
                NOTE2
                If the integer stop-code is used as the process exit status, the processor might be able to interpret only values
                within a limited range, or only a limited portion of the integer value (for example, only the least-significant 8
                bits).
1 Like

While I try to get anything but “unexpected error” from the Intel Forum (as after parsing the standard I think that even though processor-dependent it is reasonable to return a status of zero when the input value is zero for ERROR STOP) I am hoping to see results from other compilers that support ERROR STOP; and what a MicroSoft WIndows version of ifx(1) produces in particular. I currently just have ifx and gfortran available on *nix (with the results posted above). Any other results would be appreciated.

$ nvfortran --version

nvfortran 24.1-0 64-bit target on x86-64 Linux -tp rocketlake 
NVIDIA Compilers and Tools
Copyright (c) 2024, NVIDIA CORPORATION & AFFILIATES.  All rights reserved.

$ nvfortran demo_error_stop.f90 && ./a.out
NVFORTRAN-S-0034-Syntax error at or near identifier quiet (demo_error_stop.f90: 18)
NVFORTRAN/x86-64 Linux 24.1-0: compilation completed with severe errors

After removing the quiet=.false. on line 18, I get the output:

$ nvfortran demo_error_stop.f90 && ./a.out
ERROR STOP 0
[... removed lines 1-255 ...]
ERROR STOP 256
          256            0  F
1 Like

Thanks. That agrees with what is most intuitive to me and does not violate the standard (the standard stating what is returned may be processor-dependent). It seems most reasonable if STOP 0 returns 0 that ERROR STOP 0 should return zero (or not be a valid value, but it is); and 127 returning 126 looks to be a glitch I think. Any value (such as 256) subsequently returning zero weakens the case that zero returns 128 because ERROR STOP should never return a zero as well; so I want to raise the question on the Intel forum and perhaps subsequently ask for clarification on the J3 site depending on where the discussion goes.

So nvfortran(1) did not include a backtrace as part of error termination either. I was hoping that was a common result. I would actually prefer it not be produced with ERROR STOP 0 however (gfortran does it for any call to ERROR STOP as far as I can determine).