Test_StateArithmetic.pf Source File


This file depends on

sourcefile~~test_statearithmetic.pf~~EfferentGraph sourcefile~test_statearithmetic.pf Test_StateArithmetic.pf sourcefile~esmf_testmethod.f90 ESMF_TestMethod.F90 sourcefile~test_statearithmetic.pf->sourcefile~esmf_testmethod.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~test_statearithmetic.pf->sourcefile~mapl_exceptionhandling.f90 sourcefile~state_utils_setup.f90 state_utils_setup.F90 sourcefile~test_statearithmetic.pf->sourcefile~state_utils_setup.f90 sourcefile~stateutils.f90 StateUtils.F90 sourcefile~test_statearithmetic.pf->sourcefile~stateutils.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~mapl_errorhandling.f90 MAPL_ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~state_utils_setup.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~statearithmeticparser.f90 StateArithmeticParser.F90 sourcefile~stateutils.f90->sourcefile~statearithmeticparser.f90 sourcefile~statefilter.f90 StateFilter.F90 sourcefile~stateutils.f90->sourcefile~statefilter.f90 sourcefile~statemasking.f90 StateMasking.F90 sourcefile~stateutils.f90->sourcefile~statemasking.f90 sourcefile~esmf_testcase.f90->sourcefile~esmf_testparameter.f90 sourcefile~mapl_errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~statearithmeticparser.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~base_base.f90 Base_Base.F90 sourcefile~statearithmeticparser.f90->sourcefile~base_base.f90 sourcefile~fieldutils.f90 FieldUtils.F90 sourcefile~statearithmeticparser.f90->sourcefile~fieldutils.f90 sourcefile~mapl_comms.f90 MAPL_Comms.F90 sourcefile~statearithmeticparser.f90->sourcefile~mapl_comms.f90 sourcefile~statefilter.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~statefilter.f90->sourcefile~statearithmeticparser.f90 sourcefile~statefilter.f90->sourcefile~statemasking.f90 sourcefile~statefilter.f90->sourcefile~fieldutils.f90 sourcefile~statemasking.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~statemasking.f90->sourcefile~statearithmeticparser.f90 sourcefile~statemasking.f90->sourcefile~base_base.f90 sourcefile~constants.f90 Constants.F90 sourcefile~statemasking.f90->sourcefile~constants.f90 sourcefile~esmfl_mod.f90 ESMFL_Mod.F90 sourcefile~statemasking.f90->sourcefile~esmfl_mod.f90 sourcefile~mapl_keywordenforcer.f90 MAPL_KeywordEnforcer.F90 sourcefile~statemasking.f90->sourcefile~mapl_keywordenforcer.f90 sourcefile~base_base.f90->sourcefile~constants.f90 sourcefile~base_base.f90->sourcefile~mapl_keywordenforcer.f90 sourcefile~mapl_range.f90 MAPL_Range.F90 sourcefile~base_base.f90->sourcefile~mapl_range.f90 sourcefile~maplgrid.f90 MaplGrid.F90 sourcefile~base_base.f90->sourcefile~maplgrid.f90 sourcefile~internalconstants.f90 InternalConstants.F90 sourcefile~constants.f90->sourcefile~internalconstants.f90 sourcefile~mathconstants.f90 MathConstants.F90 sourcefile~constants.f90->sourcefile~mathconstants.f90 sourcefile~physicalconstants.f90 PhysicalConstants.F90 sourcefile~constants.f90->sourcefile~physicalconstants.f90 sourcefile~esmfl_mod.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~esmfl_mod.f90->sourcefile~base_base.f90 sourcefile~esmfl_mod.f90->sourcefile~constants.f90 sourcefile~esmfl_mod.f90->sourcefile~mapl_comms.f90 sourcefile~mapl_abstractgridfactory.f90 MAPL_AbstractGridFactory.F90 sourcefile~esmfl_mod.f90->sourcefile~mapl_abstractgridfactory.f90 sourcefile~mapl_gridmanager.f90 MAPL_GridManager.F90 sourcefile~esmfl_mod.f90->sourcefile~mapl_gridmanager.f90 sourcefile~fieldbinaryoperations.f90 FieldBinaryOperations.F90 sourcefile~fieldutils.f90->sourcefile~fieldbinaryoperations.f90 sourcefile~fieldblas.f90 FieldBLAS.F90 sourcefile~fieldutils.f90->sourcefile~fieldblas.f90 sourcefile~fieldpointerutilities.f90 FieldPointerUtilities.F90 sourcefile~fieldutils.f90->sourcefile~fieldpointerutilities.f90 sourcefile~fieldunaryfunctions.f90 FieldUnaryFunctions.F90 sourcefile~fieldutils.f90->sourcefile~fieldunaryfunctions.f90 sourcefile~fieldutilities.f90 FieldUtilities.F90 sourcefile~fieldutils.f90->sourcefile~fieldutilities.f90 sourcefile~mapl_comms.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_comms.f90->sourcefile~base_base.f90 sourcefile~mapl_comms.f90->sourcefile~constants.f90 sourcefile~shmem.f90 Shmem.F90 sourcefile~mapl_comms.f90->sourcefile~shmem.f90

Source Code

#include "MAPL_Generic.h"

module Test_StateArithmetic

   use state_utils_setup
   use ESMF
   use pfunit
   use MAPL_ExceptionHandling
   use MAPL_StateUtils
   use ESMF_TestMethod_mod

   implicit none

contains

   @Before
   subroutine set_up_data(this)
      class(ESMF_TestMethod), intent(inout) :: this
 
      integer :: status, rc

      grid = ESMF_GridCreateNoPeriDim(countsPerDeDim1=[3], countsPerDeDim2=[3], _RC)
      field_2d = ESMF_FieldCreate(grid, ESMF_TYPEKIND_R4, name="field_2d", _RC)
      field_3d = ESMF_FieldCreate(grid, ESMF_TYPEKIND_R4, name="field_3d",ungriddedLBound=[1],ungriddedUBound=[2], _RC)
      extra_2d = ESMF_FieldCreate(grid, ESMF_TYPEKIND_R4, name="extra_2d", _RC)
      extra_3d = ESMF_FieldCreate(grid, ESMF_TYPEKIND_R4, name="extra_3d",ungriddedLBound=[1],ungriddedUBound=[2], _RC)
      mask_field = ESMF_FieldCreate(grid, ESMF_TYPEKIND_R4, name="region_mask", _RC)
		state = ESMF_StateCreate(fieldList=[field_2d,field_3d,mask_field,extra_2d,extra_3d], _RC)

   end subroutine set_up_data

   @after
   subroutine teardown(this)
      class(ESMF_TestMethod), intent(inout) :: this
      call ESMF_FieldDestroy(field_2d, noGarbage=.true.)
      call ESMF_FieldDestroy(field_3d, noGarbage=.true.)
      call ESMF_FieldDestroy(extra_2d, noGarbage=.true.)
      call ESMF_FieldDestroy(extra_3d, noGarbage=.true.)
      call ESMF_FieldDestroy(mask_field, noGarbage=.true.)
      call ESMF_StateDestroy(state, noGarbage=.true.)
   end subroutine teardown

   @Test(type=ESMF_TestMethod, npes=[1])
   subroutine test_arithmetic_2d(this)
      class(ESMF_TestMethod), intent(inout) :: this

      integer :: status, rc
      real(ESMF_KIND_R4), pointer :: ptr2d(:,:), extra_ptr(:,:)
      real(ESMF_KIND_R4), allocatable :: expected_array(:,:)
      real(ESMF_KIND_R4) :: rval
      character(len=:), allocatable :: expr

      call ESMF_FieldGet(extra_2d, 0, farrayPtr=extra_ptr, _RC)
      call ESMF_FieldGet(field_2d, 0, farrayPtr=ptr2d, _RC)
      expr = "field_2d+2.0*sqrt(extra_2d)"
      rval = 17.0 
      ptr2d = rval
      rval = 16.0
      extra_ptr = rval
      allocate(expected_array(3,3),_STAT)
      expected_array = 17.0 + 2.0*sqrt(16.0) 
      call  MAPL_StateEval(state, expr, field_2d, _RC)
      @assertEqual(expected_array, ptr2d)
      _RETURN(_SUCCESS)

   end subroutine test_arithmetic_2d

   @Test(type=ESMF_TestMethod, npes=[1])
   subroutine test_arithmetic_3d(this)
      class(ESMF_TestMethod), intent(inout) :: this

      integer :: status, rc
      real(ESMF_KIND_R4), pointer :: ptr3d(:,:,:), extra_ptr(:,:,:)
      real(ESMF_KIND_R4), allocatable :: expected_array(:,:,:)
      real(ESMF_KIND_R4) :: rval
      character(len=:), allocatable :: expr

      call ESMF_FieldGet(extra_3d, 0, farrayPtr=extra_ptr, _RC)
      call ESMF_FieldGet(field_3d, 0, farrayPtr=ptr3d, _RC)
      expr = "field_3d+2.0*sqrt(extra_3d)"
      rval = 17.0 
      ptr3d = rval
      rval = 16.0
      extra_ptr = rval
      allocate(expected_array(3,3,2),_STAT)
      expected_array = 17.0 + 2.0*sqrt(16.0) 
      call  MAPL_StateEval(state, expr, field_3d, _RC)
      @assertEqual(expected_array, ptr3d)
      _RETURN(_SUCCESS)

   end subroutine test_arithmetic_3d

   @Test(type=ESMF_TestMethod, npes=[1])
   subroutine test_arithmetic_mixed(this)
      class(ESMF_TestMethod), intent(inout) :: this

      integer :: status, rc
      real(ESMF_KIND_R4), pointer :: ptr3d(:,:,:), extra_ptr(:,:)
      real(ESMF_KIND_R4), allocatable :: expected_array(:,:,:)
      real(ESMF_KIND_R4) :: rval
      character(len=:), allocatable :: expr

      call ESMF_FieldGet(extra_2d, 0, farrayPtr=extra_ptr, _RC)
      call ESMF_FieldGet(field_3d, 0, farrayPtr=ptr3d, _RC)
      expr = "field_3d*extra_2d"
      rval = 5.0 
      ptr3d = rval
      rval = 3.0
      extra_ptr = rval
      allocate(expected_array(3,3,2),_STAT)
      expected_array = 15.0
      call  MAPL_StateEval(state, expr, field_3d, _RC)
      @assertEqual(expected_array, ptr3d)
      _RETURN(_SUCCESS)

   end subroutine test_arithmetic_mixed

end module Test_StateArithmetic