RoutehandleManager.F90 Source File


This file depends on

sourcefile~~routehandlemanager.f90~~EfferentGraph sourcefile~routehandlemanager.f90 RoutehandleManager.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~routehandlemanager.f90->sourcefile~errorhandling.f90 sourcefile~routehandlespec.f90 RoutehandleSpec.F90 sourcefile~routehandlemanager.f90->sourcefile~routehandlespec.f90 sourcefile~routehandlespecvector.f90 RoutehandleSpecVector.F90 sourcefile~routehandlemanager.f90->sourcefile~routehandlespecvector.f90 sourcefile~routehandlevector.f90 RoutehandleVector.F90 sourcefile~routehandlemanager.f90->sourcefile~routehandlevector.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~routehandlespec.f90->sourcefile~errorhandling.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~routehandlespec.f90->sourcefile~geom_mgr.f90 sourcefile~routehandleparam.f90 RoutehandleParam.F90 sourcefile~routehandlespec.f90->sourcefile~routehandleparam.f90 sourcefile~routehandlespecvector.f90->sourcefile~routehandlespec.f90 sourcefile~geomspec.f90 GeomSpec.F90 sourcefile~geom_mgr.f90->sourcefile~geomspec.f90 sourcefile~geomutilities.f90 GeomUtilities.F90 sourcefile~geom_mgr.f90->sourcefile~geomutilities.f90 sourcefile~routehandleparam.f90->sourcefile~errorhandling.f90 sourcefile~routehandleparam.f90->sourcefile~geom_mgr.f90 sourcefile~geomutilities.f90->sourcefile~errorhandling.f90

Files dependent on this one

sourcefile~~routehandlemanager.f90~~AfferentGraph sourcefile~routehandlemanager.f90 RoutehandleManager.F90 sourcefile~esmfregridderfactory.f90 EsmfRegridderFactory.F90 sourcefile~esmfregridderfactory.f90->sourcefile~routehandlemanager.f90 sourcefile~regriddermanager.f90 RegridderManager.F90 sourcefile~regriddermanager.f90->sourcefile~esmfregridderfactory.f90 sourcefile~regridder_mgr.f90 regridder_mgr.F90 sourcefile~regridder_mgr.f90->sourcefile~regriddermanager.f90 sourcefile~regridaction.f90 RegridAction.F90 sourcefile~regridaction.f90->sourcefile~regridder_mgr.f90 sourcefile~test_regriddermanager.pf Test_RegridderManager.pf sourcefile~test_regriddermanager.pf->sourcefile~regridder_mgr.f90 sourcefile~test_routehandlemanager.pf Test_RouteHandleManager.pf sourcefile~test_routehandlemanager.pf->sourcefile~regridder_mgr.f90

Source Code

#include "MAPL_Generic.h"

! This purpose of this class is to provide a caching mechanism for
! ESMF Routehandle objects and thereby minimize the creation of
! distinct ESMF Routehandle objects during execution.  The creation of
! these objects can be expensive in terms of time and memory, so it is
! best to recognize when the objects can be used in new contexts.

! A Routehandle can be reused in any regridding scenario with the same
! in/out geometries.  At the same time there are options to
! FieldRegrid() that are independent of Routehandle which in turn
! results in the situation that distinct EsmfRegidder objects may
! utilize identical Routehandles due to the additional arguments.

! One nice thing is that since MAPL/GEOS only need a single
! EsmfRegridderFactory object, it is sensible to put a RH Manager
! object in that derived type rather than use a global object.


module mapl3g_RoutehandleManager
   use esmf
   use mapl3g_RoutehandleSpec
   use mapl3g_RoutehandleSpecVector
   use mapl3g_RoutehandleVector
   use mapl_ErrorHandlingMod
   implicit none

   public :: RoutehandleManager

   type :: RoutehandleManager
      private
      type(RoutehandleSpecVector) :: specs
      type(RoutehandleVector) :: routehandles
   contains
      procedure :: get_routehandle
      procedure :: add_routehandle
      procedure :: delete_routehandle
   end type RoutehandleManager

   interface RoutehandleManager
      module procedure :: new_RoutehandleManager
   end interface RoutehandleManager

contains

   function new_RoutehandleManager() result(mgr)
      type(RoutehandleManager) :: mgr

      mgr%specs = RoutehandleSpecVector()
      mgr%routehandles = RoutehandleVector()

   end function new_RoutehandleManager

   function get_routehandle(this, spec, rc) result(routehandle)
      type(ESMF_Routehandle) :: routehandle
      class(RoutehandleManager), target, intent(inout) :: this
      type(RoutehandleSpec), intent(in) :: spec
      integer, optional, intent(out) :: rc

      integer :: status

      associate (b => this%specs%begin(), e => this%specs%end())
        associate ( iter => find(b, e, spec))
          if (iter /= this%specs%end()) then
             routehandle = this%routehandles%of(iter - this%specs%begin() + 1)
             _RETURN(_SUCCESS)
          end if
        end associate
      end associate

      call this%add_routehandle(spec, _RC)
      routehandle = this%routehandles%back()

      _RETURN(_SUCCESS)
   end function get_routehandle


   subroutine add_routehandle(this, spec, rc)
      class(RoutehandleManager), target, intent(inout) :: this
      type(RoutehandleSpec), intent(in) :: spec
      integer, optional, intent(out) :: rc

      type(ESMF_Routehandle) :: routehandle
      integer :: status

      associate (b => this%specs%begin(), e => this%specs%end())
          _ASSERT(find(b, e, spec) == e, "Spec already exists in registry.")
      end associate

      routehandle = make_routehandle(spec, _RC)

      call this%specs%push_back(spec)
      call this%routehandles%push_back(routehandle)

      _RETURN(_SUCCESS)
   end subroutine add_routehandle

   
   subroutine delete_routehandle(this, spec, rc)
      class(RoutehandleManager), intent(inout) :: this
      type(RoutehandleSpec), intent(in) :: spec
      integer, optional, intent(out) :: rc

      type(RoutehandleSpecVectorIterator) :: iter
      type(RoutehandleVectorIterator) :: rh_iter
      associate (b => this%specs%begin(), e => this%specs%end())
        iter = find(b, e, spec)
        _ASSERT(iter /= e, "Spec not found in registry.")

        iter = this%specs%erase(iter)
        rh_iter = this%routehandles%begin() + (iter - b)
        rh_iter = this%routehandles%erase(rh_iter)

      end associate

      _RETURN(_SUCCESS)
   end subroutine delete_routehandle

end module mapl3g_RoutehandleManager