VOLATILE: needed?

I have a wrapper to C to control a Fortran program with IPC signals (Signal (IPC) - Wikipedia). The code is the following

/* c_interface.c */
#include <signal.h>

void signalterm_c(void (*handler)(int)){
  signal(SIGTERM, handler);
}

void signalusr1_c(void (*handler)(int)){
  signal(SIGUSR1, handler);
}
! c_interface.f90
module c_interface

  implicit none
  interface

  subroutine signalterm_C(handler) bind(C)
    use, intrinsic :: ISO_C_Binding, only: C_FUNPTR

    type(C_FUNPTR), intent(in), value :: handler
  end subroutine signalterm_C

  subroutine signalusr1_C(handler) bind(C)
    use, intrinsic :: ISO_C_Binding, only: C_FUNPTR

    type(C_FUNPTR), intent(in), value :: handler
  end subroutine signalusr1_C

  end interface

end module c_interface
! wait_for_SIGTERM.f90
program wait_for_SIGTERM
  use, intrinsic :: ISO_C_binding

  use c_interface

  implicit none
  logical, volatile :: &
    interface_SIGTERM, &                                                                            !< termination signal
    interface_SIGUSR1                                                                            !< 1. user-defined signal

  call init

  do while( .not. interface_SIGTERM)


  enddo

contains

subroutine init()

  call signalterm_c(c_funloc(catchSIGTERM))
  call signalusr1_c(c_funloc(catchSIGUSR1))
  call interface_setSIGTERM(.false.)
  call interface_setSIGUSR1(.false.)

end subroutine init

!--------------------------------------------------------------------------------------------------
!> @brief Set global variable interface_SIGTERM to .true.
!> @details This function can be registered to catch signals send to the executable.
!--------------------------------------------------------------------------------------------------
subroutine catchSIGTERM(signal) bind(C)

  integer(C_INT), value :: signal


  print'(a,i0)', ' received signal ',signal
  call interface_setSIGTERM(.not. interface_SIGTERM)

end subroutine catchSIGTERM


!--------------------------------------------------------------------------------------------------
!> @brief Set global variable interface_SIGUSR1 to .true.
!> @details This function can be registered to catch signals send to the executable.
!--------------------------------------------------------------------------------------------------
subroutine catchSIGUSR1(signal) bind(C)

  integer(C_INT), value :: signal


  print'(a,i0)', ' received signal ',signal
  call interface_setSIGUSR1(.not. interface_SIGUSR1)

end subroutine catchSIGUSR1


!--------------------------------------------------------------------------------------------------
!> @brief Set global variable interface_SIGTERM.
!--------------------------------------------------------------------------------------------------
subroutine interface_setSIGTERM(state)

  logical, intent(in) :: state


  interface_SIGTERM = state
  print*, 'set SIGTERM to',state

end subroutine interface_setSIGTERM


!--------------------------------------------------------------------------------------------------
!> @brief Set global variable interface_SIGUSR.
!--------------------------------------------------------------------------------------------------
subroutine interface_setSIGUSR1(state)

  logical, intent(in) :: state


  interface_SIGUSR1 = state
  print*, 'set SIGUSR1 to',state

end subroutine interface_setSIGUSR1

end program

Compile with gfortran and run (tested on Linux):

gfortran c_interface.c c_interface.f90 wait_for_SIGTERM.f90 -o wait
./wait&
kill -SIGUSR1 XXXX
kill -SIGUSR1 XXXX
kill -SIGTERM XXXX

where XXXX is the process ID (printed after running wait).

My question is now: Is it required that interface_SIGTERM and interface_SIGUSR1 have the VOLATILE attribute? They are only changed by interface_setSIGTERM and interface_setSIGUSR1, but these setters are not called from within the program. I would not be surprised if an aggressive compiler removes the while loop in the main program.

The observed behavior is

  • gfortran without optimization flag: Enters loop and leaves (independently of VOLATILE)
  • gfortran -O3: Enters loop, but never leaves it.
  • ifort/icc without optimization flag and with -O3: Enters loop, never leaves it without VOLATILE, leaves if VOLATILE.

The standard says:

8.5.19 VOLATILE attribute
The VOLATILE attribute specifies that an object may be referenced, defined, or become undefined, by means not specified by the program.

1 Like

Yes, VOLATILE is required in this context. What happens when you omit it all depends on how the selected compiler chooses to optimize.

4 Likes