caffeine_assert_s.F90 Source File


This file depends on

sourcefile~~caffeine_assert_s.f90~~EfferentGraph sourcefile~caffeine_assert_s.f90 caffeine_assert_s.F90 sourcefile~prif_private_s.f90 prif_private_s.f90 sourcefile~caffeine_assert_s.f90->sourcefile~prif_private_s.f90 sourcefile~prif.f90 prif.F90 sourcefile~prif_private_s.f90->sourcefile~prif.f90

Contents

Source Code


Source Code

! Copyright (c), The Regents of the University of California
! Terms of use are as specified in LICENSE.txt
submodule(prif:prif_private_s) caffeine_assert_s
  implicit none

#if CAF_ASSERTIONS || !defined(CAF_ASSERTIONS)
  logical, parameter :: assertions_=.true.
#else
  logical, parameter :: assertions_=.false.
#endif

   !! Disable assertions by compiling with preprocessor setting: -DCAF_ASSERTIONS=0

contains

  module procedure assert
    character(len=:), allocatable :: tail

    if (assertions_) then 
      if (.not. assertion) then
        if (.not. present(diagnostics)) then
          tail = "."
        else
          tail = " with diagnostics "
          select type(diagnostics)
            type is(character(len=*))
              tail = tail // diagnostics
            class default
              tail = tail // "of unsupported type."
          end select
        end if

        call prif_error_stop(.false._c_bool, stop_code_char='Assertion "'// description // '" failed' // tail)
      end if
    end if
  end procedure

end submodule caffeine_assert_s