assertions_interface.F90 Source File


Files dependent on this one

sourcefile~~assertions_interface.f90~~AfferentGraph sourcefile~assertions_interface.f90 assertions_interface.F90 sourcefile~units_implementation.f90 units_implementation.F90 sourcefile~units_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~array_functions_implementation.f90 array_functions_implementation.f90 sourcefile~array_functions_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~spherical_1d_solver_submodule.f90 spherical_1D_solver_submodule.F90 sourcefile~spherical_1d_solver_submodule.f90->sourcefile~assertions_interface.f90 sourcefile~problem_discretization_implementation.f90 problem_discretization_implementation.F90 sourcefile~problem_discretization_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~cylinder_2d_implementation.f90 cylinder_2D_implementation.F90 sourcefile~cylinder_2d_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~structured_grid_implementation.f90 structured_grid_implementation.F90 sourcefile~structured_grid_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~emulated_intrinsics_implementation.f90 emulated_intrinsics_implementation.F90 sourcefile~emulated_intrinsics_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~surfaces_implementation.f90 surfaces_implementation.F90 sourcefile~surfaces_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~sphere_1d_implementation.f90 sphere_1D_implementation.F90 sourcefile~sphere_1d_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~cylindrical_grid_implementation.f90 cylindrical_grid_implementation.f90 sourcefile~cylindrical_grid_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~plate_3d_implementation.f90 plate_3D_implementation.F90 sourcefile~plate_3d_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~cartesian_grid_implementation.f90 cartesian_grid_implementation.f90 sourcefile~cartesian_grid_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~assertions_implementation.f90 assertions_implementation.F90 sourcefile~assertions_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~package_implementation.f90 package_implementation.F90 sourcefile~package_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~grid_implementation.f90 grid_implementation.f90 sourcefile~grid_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~ellipsoidal_field_implementation.f90 ellipsoidal_field_implementation.f90 sourcefile~ellipsoidal_field_implementation.f90->sourcefile~assertions_interface.f90 sourcefile~spherical_grid_implementation.f90 spherical_grid_implementation.f90 sourcefile~spherical_grid_implementation.f90->sourcefile~assertions_interface.f90

Contents


Source Code

!
!     (c) 2019-2020 Guide Star Engineering, LLC
!     This Software was developed for the US Nuclear Regulatory Commission (US NRC) under contract
!     "Multi-Dimensional Physics Implementation into Fuel Analysis under Steady-state and Transients (FAST)",
!     contract # NRC-HQ-60-17-C-0007
!
#ifndef USE_ASSERTIONS
# define USE_ASSERTIONS .false.
#endif
module assertions_interface
  !! summary: Utility for runtime checking of logical assertions.
  !!
  !! Compile with -DNO_ASSERTIONS to turn assertions off
  !!
  !! Use case 1
  !! ----------
  !!    Pass the optional success argument & check for false return value as an indication of assertion failure:
  !!
  !!    use assertions_interface, only : assert,assertions
  !!    if (assertions) call assert( 2 > 1, "always true inequality", success)
  !!    if (error_code/=0) call my_error_handler()
  !!
  !! Use case 2
  !! ----------
  !!    Error-terminate if the assertion fails:
  !!
  !!    use assertions_interface, only : assert,assertions
  !!    if (assertions) call assert( 2 > 1, "always true inequality")
  !!
  implicit none
  private
  public :: assert
  public :: assertions
  public :: max_errmsg_len

! Set the USE_ASSERTIONS constant below using the C preprocessor:
!
!    gfortran -cpp -DUSE_ASSERTIONS=.false. -c assertions_interface.f90
!
! or set the corresponding NO_ASSERTIONS variable defined in the CMakeLists.txt file in this directory:
!
!    FC=caf cmake <path-to-icar-source-dir> -DNO_ASSERTIONS=ON
!
! Conditioning assertion calls on this compile-time constant enables optimizing compilers
! to eliminate assertion calls during a dead-code removal phase of optimization.

  logical, parameter :: assertions=USE_ASSERTIONS
  integer, parameter :: max_errmsg_len = len( &
  "warning (183): FASTMEM allocation is requested but the libmemkind library is not linked in, so using the default allocator.")
  !! longest Intel compiler error messagea (see https://intel.ly/35x84yr).

  interface
#ifndef HAVE_ERROR_STOP_IN_PURE
    impure &
#endif
    elemental module subroutine assert(assertion,description,diagnostic_data,success)
      !! Report on the truth of an assertion or error-terminate on assertion failure
      implicit none
      logical, intent(in) :: assertion
        !! Most assertions will be expressions, e.g., call assert( i>0, "positive i")
      character(len=*), intent(in) :: description
        !! Brief statement of what is being asserted
      class(*), intent(in), optional :: diagnostic_data
        !! Optional assertion result
      logical, intent(out), optional :: success
        !! Optional assertion result
    end subroutine
  end interface
end module