ESMF_TestMethod.F90 Source File


This file depends on

sourcefile~~esmf_testmethod.f90~~EfferentGraph sourcefile~esmf_testmethod.f90 ESMF_TestMethod.F90 sourcefile~esmf_testcase.f90 ESMF_TestCase.F90 sourcefile~esmf_testmethod.f90->sourcefile~esmf_testcase.f90 sourcefile~esmf_testparameter.f90 ESMF_TestParameter.F90 sourcefile~esmf_testmethod.f90->sourcefile~esmf_testparameter.f90 sourcefile~esmf_testcase.f90->sourcefile~esmf_testparameter.f90

Files dependent on this one

sourcefile~~esmf_testmethod.f90~~AfferentGraph sourcefile~esmf_testmethod.f90 ESMF_TestMethod.F90 sourcefile~test_cfio_bundle.pf Test_CFIO_Bundle.pf 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_latlon_corners.pf Test_LatLon_Corners.pf 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_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_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

module ESMF_TestMethod_mod
   use pFUnit
   use ESMF
   use ESMF_TestCase_mod
   use ESMF_TestParameter_mod
   implicit none
   private

   public :: ESMF_TestMethod

   type, extends(ESMF_TestCase) :: ESMF_TestMethod
      procedure(esmfMethod), pointer :: userMethod => null()
      procedure(esmfMethod), pointer :: userSetUp => null()
      procedure(esmfMethod), pointer :: userTearDown => null()
   contains
      procedure :: runMethod
      procedure :: setUp
      procedure :: tearDown
   end type ESMF_TestMethod

   abstract interface
      subroutine esmfMethod(this)
         import ESMF_TestMethod
         class (ESMF_TestMethod), intent(inout) :: this
      end subroutine esmfMethod
   end interface

   interface Esmf_TestMethod
      module procedure newEsmf_TestMethod_basic
      module procedure newEsmf_TestMethod_setUpTearDown
   end interface Esmf_TestMethod

contains

   
   function newEsmf_TestMethod_basic(name, userMethod, numPETs) result(esmf_Test)
      character(len=*), intent(in) :: name
      procedure (runMethod) :: userMethod
      integer, intent(in) :: numPETs
      type (Esmf_TestMethod), target :: esmf_Test

      call esmf_Test%setName(name)
      esmf_Test%userMethod => userMethod
      call esmf_Test%setTestParameter(ESMF_TestParameter(numPETs))


   end function newEsmf_TestMethod_basic

   function newEsmf_TestMethod_setUpTearDown(name, userMethod, numPETs, setUp, tearDown) result(esmf_Test)
      character(len=*), intent(in) :: name
      procedure (runMethod) :: userMethod
      integer, intent(in) :: numPETs
      type (Esmf_TestMethod), target :: esmf_Test
      procedure (runMethod) :: setUp
      procedure (runMethod) :: tearDown

      call esmf_Test%setName(name)
      esmf_Test%userMethod => userMethod
      call esmf_Test%setTestParameter(ESMF_TestParameter(numPETs))

      esmf_Test%userSetUp => setUp
      esmf_Test%userTearDown => tearDown


   end function newEsmf_TestMethod_setUpTearDown


   subroutine setUp(this)
      class (ESMF_TestMethod), intent(inout) :: this

      if (associated(this%userSetUp)) then
         call this%userSetUp()
      end if

   end subroutine setUp


   subroutine runMethod(this)
      class (ESMF_TestMethod), intent(inout) :: this

      call this%userMethod()
   end subroutine runMethod


   subroutine tearDown(this)
      class (ESMF_TestMethod), intent(inout) :: this

      if (associated(this%userTearDown)) then
         call this%userTearDown()
      end if

   end subroutine tearDown

end module ESMF_TestMethod_mod