ESMF_TestParameter.F90 Source File


Files dependent on this one

sourcefile~~esmf_testparameter.f90~~AfferentGraph sourcefile~esmf_testparameter.f90 ESMF_TestParameter.F90 sourcefile~esmf_testcase.f90 ESMF_TestCase.F90 sourcefile~esmf_testcase.f90->sourcefile~esmf_testparameter.f90 sourcefile~esmf_testmethod.f90 ESMF_TestMethod.F90 sourcefile~esmf_testmethod.f90->sourcefile~esmf_testparameter.f90 sourcefile~esmf_testmethod.f90->sourcefile~esmf_testcase.f90 sourcefile~test_latlon_corners.pf Test_LatLon_Corners.pf sourcefile~test_latlon_corners.pf->sourcefile~esmf_testparameter.f90 sourcefile~test_latlon_corners.pf->sourcefile~esmf_testcase.f90 sourcefile~test_latlon_corners.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_latlon_gridfactory.pf Test_LatLon_GridFactory.pf sourcefile~test_latlon_gridfactory.pf->sourcefile~esmf_testparameter.f90 sourcefile~test_latlon_gridfactory.pf->sourcefile~esmf_testcase.f90 sourcefile~test_latlon_gridfactory.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_scenarios.pf Test_Scenarios.pf sourcefile~test_scenarios.pf->sourcefile~esmf_testparameter.f90 sourcefile~test_scenarios.pf->sourcefile~esmf_testcase.f90 sourcefile~test_cfio_bundle.pf Test_CFIO_Bundle.pf sourcefile~test_cfio_bundle.pf->sourcefile~esmf_testcase.f90 sourcefile~test_cfio_bundle.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_fixedlevelsverticalgrid.pf Test_FixedLevelsVerticalGrid.pf sourcefile~test_fixedlevelsverticalgrid.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_geommanager.pf Test_GeomManager.pf sourcefile~test_geommanager.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_regriddermanager.pf Test_RegridderManager.pf sourcefile~test_regriddermanager.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_routehandlemanager.pf Test_RouteHandleManager.pf sourcefile~test_routehandlemanager.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_simplemaplcomp.pf Test_SimpleMAPLcomp.pf sourcefile~test_simplemaplcomp.pf->sourcefile~esmf_testcase.f90 sourcefile~test_simplemaplcomp.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_sphericaltocartesian.pf Test_SphericalToCartesian.pf sourcefile~test_sphericaltocartesian.pf->sourcefile~esmf_testmethod.f90 sourcefile~test_stateregistry.pf Test_StateRegistry.pf sourcefile~test_stateregistry.pf->sourcefile~esmf_testmethod.f90

Source Code

#include "unused_dummy.H"

module ESMF_TestParameter_mod
   use pfunit, only: MpiTestParameter
   implicit none

   private

   public :: ESMF_TestParameter
   
   type, extends(MpiTestParameter) :: ESMF_TestParameter
      integer :: numPETsRequested
   contains
      procedure :: setNumPetsRequested
      procedure :: getNumPetsRequested
      procedure :: toString
      procedure :: toStringActual
   end type ESMF_TestParameter

   interface ESMF_TestParameter
      module procedure :: newESMF_TestParameter
   end interface ESMF_TestParameter

contains

   !---------------------------------
   ! TestParameter procedures
   !---------------------------------
   
   ! Note that npes requested may not be available. 
   function newESMF_TestParameter(numPEtsRequested) result(testParameter)
      type (ESMF_TestParameter) :: testParameter
      integer, intent(in) :: numPETsRequested
      
      call testParameter%setNumPETsRequested(numPETsRequested)
      
   end function newESMF_TestParameter

   pure subroutine setNumPETsRequested(this, numPETsRequested)
      class (ESMF_TestParameter), intent(inout) :: this
      integer, intent(in) :: numPETsRequested
      this%numPETsRequested = numPETsRequested
   end subroutine setNumPETsRequested


   ! This function ensures that "npes = #" is included in the message string 
   ! for each exception.   It should rarely be overridden.
   function toStringActual(this) result(string)
      class (ESMF_TestParameter), intent(in) :: this
      character(:), allocatable :: string

      character(len=8) :: numPETsString
      character(:), allocatable :: tmp

      write(numPETsString,'(i0)') this%numPETsRequested

      string = 'numPETs=' // trim(numPETsString) 
      tmp = this%toString()

      if (len_trim(tmp) > 0) then
         string = string // ' :: ' // trim(tmp)
      end if

   end function toStringActual

   
   ! Provide a default empty string.  It is expected that this function
   ! will be overridden for user defined test cases.
   function toString(this) result(string)
      class (ESMF_TestParameter), intent(in) :: this
      character(:), allocatable :: string
      _UNUSED_DUMMY(this)

      string = ''

   end function toString


   pure integer function getNumPETsRequested(this) result(numPETsRequested)
      class (ESMF_TestParameter), intent(in) :: this
      numPETsRequested = this%numPETsRequested
   end function getNumPETsRequested

   
end module ESMF_TestParameter_mod