MaxAction.F90 Source File


This file depends on

sourcefile~~maxaction.f90~~EfferentGraph sourcefile~maxaction.f90 MaxAction.F90 sourcefile~accumulatoraction.f90 AccumulatorAction.F90 sourcefile~maxaction.f90->sourcefile~accumulatoraction.f90 sourcefile~fieldpointerutilities.f90 FieldPointerUtilities.F90 sourcefile~maxaction.f90->sourcefile~fieldpointerutilities.f90 sourcefile~internalconstants.f90 InternalConstants.F90 sourcefile~maxaction.f90->sourcefile~internalconstants.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~maxaction.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~accumulatoraction.f90->sourcefile~fieldpointerutilities.f90 sourcefile~accumulatoraction.f90->sourcefile~internalconstants.f90 sourcefile~accumulatoraction.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~extensionaction.f90 ExtensionAction.F90 sourcefile~accumulatoraction.f90->sourcefile~extensionaction.f90 sourcefile~fieldutilities.f90 FieldUtilities.F90 sourcefile~accumulatoraction.f90->sourcefile~fieldutilities.f90 sourcefile~fieldpointerutilities.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~extensionaction.f90->sourcefile~errorhandling.f90 sourcefile~fieldutilities.f90->sourcefile~fieldpointerutilities.f90 sourcefile~fieldutilities.f90->sourcefile~errorhandling.f90 sourcefile~fieldinfo.f90 FieldInfo.F90 sourcefile~fieldutilities.f90->sourcefile~fieldinfo.f90 sourcefile~infoutilities.f90 InfoUtilities.F90 sourcefile~fieldutilities.f90->sourcefile~infoutilities.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~fieldutilities.f90->sourcefile~keywordenforcer.f90 sourcefile~lu_bound.f90 LU_Bound.F90 sourcefile~fieldutilities.f90->sourcefile~lu_bound.f90 sourcefile~ungriddeddims.f90 UngriddedDims.F90 sourcefile~fieldutilities.f90->sourcefile~ungriddeddims.f90 sourcefile~fieldinfo.f90->sourcefile~errorhandling.f90 sourcefile~fieldinfo.f90->sourcefile~infoutilities.f90 sourcefile~fieldinfo.f90->sourcefile~keywordenforcer.f90 sourcefile~fieldinfo.f90->sourcefile~ungriddeddims.f90 sourcefile~mapl_esmf_infokeys.f90 MAPL_ESMF_InfoKeys.F90 sourcefile~fieldinfo.f90->sourcefile~mapl_esmf_infokeys.f90 sourcefile~verticalstaggerloc.f90 VerticalStaggerLoc.F90 sourcefile~fieldinfo.f90->sourcefile~verticalstaggerloc.f90 sourcefile~infoutilities.f90->sourcefile~errorhandling.f90 sourcefile~infoutilities.f90->sourcefile~keywordenforcer.f90 sourcefile~infoutilities.f90->sourcefile~mapl_esmf_infokeys.f90 sourcefile~ungriddeddims.f90->sourcefile~errorhandling.f90 sourcefile~ungriddeddims.f90->sourcefile~infoutilities.f90 sourcefile~ungriddeddims.f90->sourcefile~lu_bound.f90 sourcefile~ungriddeddims.f90->sourcefile~mapl_esmf_infokeys.f90 sourcefile~ungriddeddim.f90 UngriddedDim.F90 sourcefile~ungriddeddims.f90->sourcefile~ungriddeddim.f90 sourcefile~ungriddeddimvector.f90 UngriddedDimVector.F90 sourcefile~ungriddeddims.f90->sourcefile~ungriddeddimvector.f90

Files dependent on this one

sourcefile~~maxaction.f90~~AfferentGraph sourcefile~maxaction.f90 MaxAction.F90 sourcefile~test_maxaction.pf Test_MaxAction.pf sourcefile~test_maxaction.pf->sourcefile~maxaction.f90

Source Code

#include "MAPL_Generic.h"
module mapl3g_MaxAction
   use mapl3g_AccumulatorAction
   use MAPL_ExceptionHandling
   use MAPL_InternalConstantsMod, only: MAPL_UNDEFINED_REAL, MAPL_UNDEFINED_REAL64
   use MAPL_FieldPointerUtilities, only: assign_fptr
   use ESMF
   implicit none
   private
   public :: MaxAction

   type, extends(AccumulatorAction) :: MaxAction
   contains
      procedure :: accumulate_R4 => max_accumulate_R4
   end type MaxAction

   interface MaxAction
      module procedure :: construct_MaxAction
   end interface MaxAction

contains

   function construct_MaxAction() result(acc)
      type(MaxAction) :: acc

      acc%CLEAR_VALUE_R4 = MAPL_UNDEFINED_REAL

   end function construct_MaxAction

   subroutine max_accumulate_R4(this, update_field, rc)
      class(MaxAction), intent(inout) :: this
      type(ESMF_Field), intent(inout) :: update_field
      integer, optional, intent(out) :: rc

      integer :: status
      real(kind=ESMF_KIND_R4), pointer :: current(:)
      real(kind=ESMF_KIND_R4), pointer :: latest(:)
      real(kind=ESMF_KIND_R4), parameter :: UNDEF = MAPL_UNDEFINED_REAL

      call assign_fptr(this%accumulation_field, current, _RC)
      call assign_fptr(update_field, latest, _RC)
      where(current == UNDEF)
         current = latest
      elsewhere(latest /= UNDEF)
         current = max(current, latest)
      end where
      _RETURN(_SUCCESS)

   end subroutine max_accumulate_R4

end module mapl3g_MaxAction