runtime_tests.fpp Source File


Contents

Source Code


Source Code

#include "define.inc"

!>  This module is intended to be used for runtime tests
!!  which interrogate what is functional/what compile time
!!  options were enabled/disabled, and also any enviroment variables
!!  which affect what happens at runtime.
module runtime_tests

  implicit none

  private

  public :: runtime_info

! Functions provided for backwards compatibility
  public :: build_identifier
  public :: compiler_pgi
  public :: get_git_hash
  public :: get_git_modified
  public :: is_release
  public :: release
  public :: verbosity

  !> Type providing information about the code version, compiler, build
  !! environment etc
  type :: runtime_info_type

    private
    !> Integer determining the verbosity of debugging output, with higher
    !! values being more verbose. `verbosity` is read from the
    !! GK_VERBOSITY environment variable
    integer :: verbosity
    !> Whether verbosity has already been read from the environment variable.
    !! Reading environment variables is moderately expensive, so this is done
    !! once and the value stored in [[verbosity]].
    logical :: verbosity_initialized = .false.

    contains
    !> Get the value of [[verbosity]], reading the enviroment variable
    !! GK_VERBOSITY if necessary.
    procedure :: get_verbosity
    !> Returns whether current version is a release
    procedure, nopass :: is_release => is_release_runtime_info
    !> Returns the release number
    procedure, nopass :: release => release_runtime_info
    !> Returns whether a PGI compiler was used
    procedure, nopass :: compiler_pgi => compiler_pgi_runtime_info
    !> Returns the name of the compiler used
    procedure, nopass :: get_compiler_name
    !> Returns the value of the GK_SYSTEM environment variable
    procedure, nopass :: get_gk_system
    !> Returns an identifier of the system and build:
    !! "system.compiler.githash".
    procedure :: build_identifier => build_identifier_runtime_info
    !> Returns the git hash
    procedure, nopass :: get_git_hash => get_git_hash_runtime_info
    !> Returns whether the source code has been modified relative to the
    !! repository version
    procedure, nopass :: get_git_modified => get_git_modified_runtime_info

  end type runtime_info_type

  type(runtime_info_type) runtime_info

contains


!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!  Tests for compilers
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  !> Returns whether a PGI compiler was used
  function compiler_pgi_runtime_info()
    implicit none
    logical :: compiler_pgi_runtime_info
    compiler_pgi_runtime_info = .false.
#if FCOMPILER == _PGI_
    compiler_pgi_runtime_info = .true.
#endif
  end function compiler_pgi_runtime_info

  !> Returns the name of the compiler used
  function get_compiler_name()
    implicit none
    character(len=9) :: get_compiler_name
    get_compiler_name='unknown'
#if FCOMPILER == _PGI_
    get_compiler_name='pgi'
#elif FCOMPILER == _INTEL_
    get_compiler_name='intel'
#elif FCOMPILER == _IFX_
    get_compiler_name='ifx'
#elif FCOMPILER == _GFORTRAN_
    get_compiler_name='gfortran'
#elif FCOMPILER == _XL_
    get_compiler_name='xl'
#elif FCOMPILER == _NAG_
    get_compiler_name='nag'
#elif FCOMPILER == _CRAY_
    get_compiler_name='cray'
#elif FCOMPILER == _G95_
    get_compiler_name='g95'
#elif FCOMPILER == _PATHSCALE_
    get_compiler_name='pathscale'
#elif FCOMPILER == _LAHEY_
    get_compiler_name='lahey'
#elif FCOMPILER == _ABSOFT_
    get_compiler_name='absoft'
#elif FCOMPILER == _ALPHA_
    get_compiler_name='alpha'
#elif FCOMPILER == _SUN_
    get_compiler_name='sun'
#elif FCOMPILER == _FUJ_
    get_compiler_name='fujitsu'
#elif FCOMPILER == _NEC_
    get_compiler_name='nec'
#endif
  end function get_compiler_name

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!


!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!  Tests for git info
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  !> Returns the git hash
  function get_git_hash_runtime_info(length_in)
    implicit none
    integer, optional, intent(in) :: length_in
    integer :: length = 40
    character(len=40) :: get_git_hash_runtime_info

    if( present(length_in) ) then
      if( length_in <= 40 ) then
        length = length_in
      end if
    end if

#ifndef GIT_HASH
#define GIT_HASH "unknown"
    length=7
#endif
    get_git_hash_runtime_info=GIT_HASH(1:length)
  end function get_git_hash_runtime_info

  !> Returns whether the source code has been modified relative to the
  !! repository version
  function get_git_modified_runtime_info()
    implicit none
    logical :: get_git_modified_runtime_info
#ifndef GIT_HASH
#define GIT_HASH "unknown"
#endif
    if(GIT_STATE.eq."clean")then
       get_git_modified_runtime_info=.false.
    else
       get_git_modified_runtime_info=.true.
    endif
  end function get_git_modified_runtime_info
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! System info
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  !> Returns the value of the GK_SYSTEM environment variable
  function get_gk_system()
    implicit none
    character(len=20) :: get_gk_system
#ifndef GK_SYSTEM
#define GK_SYSTEM "unknown"
#endif
    get_gk_system=GK_SYSTEM
  end function get_gk_system

  !> Returns an identifier of the system and build:
  !! "system.compiler.githash".
  function build_identifier_runtime_info(self)
    implicit none
    class(runtime_info_type), intent(inout) :: self
    character(len=50) :: build_identifier_runtime_info
    character(len=:), allocatable :: git_hash

    git_hash = self%get_git_hash(7)
    build_identifier_runtime_info = trim(self%get_gk_system())&
         //"."//trim(self%get_compiler_name())&
         //'.'//git_hash(1:7)

    if(self%get_git_modified()) then
      build_identifier_runtime_info = trim(build_identifier_runtime_info(1:41))//'.modified'
    end if

  end function build_identifier_runtime_info

  !> Returns whether current version is a release
  function is_release_runtime_info()
    implicit none
    logical :: is_release_runtime_info
#ifdef IS_RELEASE
    is_release_runtime_info = .true.
#else
    is_release_runtime_info = .false.
#endif
  end function is_release_runtime_info

  !> Returns the release number
  function release_runtime_info()
    implicit none
    character(len=30) :: release_runtime_info
#ifdef RELEASE
    release_runtime_info = RELEASE
#else
    release_runtime_info = 'no known release'
#endif
  end function release_runtime_info

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! Testing the runtime environment
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  !> This function interrogates the environment variable
  !! GK_VERBOSITY and returns its integer value. This is used
  !! to control the level of debug output (not diagnostic/physics output).
  !! Normal levels range from 0 to 5, with output getting 
  !! heavier as the value increases. Values higher than 5 can be used for 
  !! specialised/very heavy output.
  function get_verbosity(self)
    implicit none
    class(runtime_info_type), intent(inout) :: self
    integer :: get_verbosity
    character(len=10) :: verbosity_char

    if( self%verbosity_initialized ) then
      get_verbosity = self%verbosity
    else
      verbosity_char = ''
      call get_environment_variable("GK_VERBOSITY", verbosity_char)
      read (verbosity_char,'(I10)') get_verbosity
      self%verbosity = get_verbosity
      self%verbosity_initialized = .true.
    end if
  end function get_verbosity

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! Functions provided for backwards compatibility !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  !> This function is just a call of [[get_verbosity]] and is provided for
  !! backwards compatibility.
  function verbosity()
    implicit none
    integer :: verbosity

    verbosity = runtime_info%get_verbosity()

  end function verbosity

  !> This function is just a call of [[is_release_runtime_info]] and is provided for
  !! backwards compatibility.
  function is_release()
    implicit none
    logical :: is_release

    is_release = runtime_info%is_release()

  end function is_release

  !> This function is just a call of [[release_runtime_info]] and is provided for
  !! backwards compatibility.
  function release()
    implicit none
    character(len=30) :: release

    release = runtime_info%release()

  end function release

  !> This function is just a call of [[get_git_hash_runtime_info]] and is provided for
  !! backwards compatibility.
  function get_git_hash(length_in)
    implicit none
    integer, optional, intent(in) :: length_in
    character(len=40) :: get_git_hash

    get_git_hash = runtime_info%get_git_hash(length_in)

  end function get_git_hash

  !> This function is just a call of [[get_git_modified_runtime_info]] and is provided for
  !! backwards compatibility.
  function get_git_modified()
    implicit none
    logical :: get_git_modified

    get_git_modified = runtime_info%get_git_modified()

  end function get_git_modified

  !> This function is just a call of [[build_identifier_runtime_info]] and is provided for
  !! backwards compatibility.
  function build_identifier()
    implicit none
    character(len=50) :: build_identifier

    build_identifier = runtime_info%build_identifier()

  end function build_identifier

  !> This function is just a call of [[compiler_pgi_runtime_info]] and is provided for
  !! backwards compatibility.
  function compiler_pgi()
    implicit none
    logical :: compiler_pgi

    compiler_pgi = runtime_info%compiler_pgi()

  end function compiler_pgi

end module runtime_tests