EsmfRegridderFactory.F90 Source File


This file depends on

sourcefile~~esmfregridderfactory.f90~~EfferentGraph sourcefile~esmfregridderfactory.f90 EsmfRegridderFactory.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~esmfregridderfactory.f90->sourcefile~errorhandling.f90 sourcefile~nullregridder.f90 NullRegridder.F90 sourcefile~esmfregridderfactory.f90->sourcefile~nullregridder.f90 sourcefile~regridderfactory.f90 RegridderFactory.F90 sourcefile~esmfregridderfactory.f90->sourcefile~regridderfactory.f90 sourcefile~regridderparam.f90 RegridderParam.F90 sourcefile~esmfregridderfactory.f90->sourcefile~regridderparam.f90 sourcefile~regridderspec.f90~2 RegridderSpec.F90 sourcefile~esmfregridderfactory.f90->sourcefile~regridderspec.f90~2 sourcefile~routehandlemanager.f90 RoutehandleManager.F90 sourcefile~esmfregridderfactory.f90->sourcefile~routehandlemanager.f90 sourcefile~routehandleparam.f90 RoutehandleParam.F90 sourcefile~esmfregridderfactory.f90->sourcefile~routehandleparam.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~nullregridder.f90->sourcefile~errorhandling.f90 sourcefile~regridderspec.f90~2->sourcefile~regridderparam.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~regridderspec.f90~2->sourcefile~geom_mgr.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~routehandleparam.f90->sourcefile~errorhandling.f90 sourcefile~routehandleparam.f90->sourcefile~geom_mgr.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~routehandlespec.f90->sourcefile~errorhandling.f90 sourcefile~routehandlespec.f90->sourcefile~routehandleparam.f90 sourcefile~routehandlespec.f90->sourcefile~geom_mgr.f90 sourcefile~routehandlespecvector.f90->sourcefile~routehandlespec.f90 sourcefile~geomutilities.f90->sourcefile~errorhandling.f90

Files dependent on this one

sourcefile~~esmfregridderfactory.f90~~AfferentGraph sourcefile~esmfregridderfactory.f90 EsmfRegridderFactory.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 sourcefile~fieldspec.f90~2 FieldSpec.F90 sourcefile~fieldspec.f90~2->sourcefile~regridaction.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_EsmfRegridderFactory
   use mapl3g_RegridderFactory
   use mapl3g_Regridder
   use mapl3g_RoutehandleParam
   use mapl3g_RoutehandleManager
   use mapl3g_EsmfRegridder
   use mapl3g_RegridderParam
   use mapl3g_RegridderSpec
   use mapl3g_NullRegridder
   use mapl_ErrorHandlingMod
   implicit none
   private
   
   public :: EsmfRegridderFactory

   type, extends(RegridderFactory) :: EsmfRegridderFactory
      private
      type(RoutehandleManager) :: rh_manager
   contains
      procedure :: supports
      procedure :: make_regridder_typesafe
   end type EsmfRegridderFactory

   interface EsmfRegridderFactory
      procedure :: new_EsmfRegridderFactory
   end interface EsmfRegridderFactory

contains

   function new_EsmfRegridderFactory() result(factory)
      type(EsmfRegridderFactory) :: factory

      factory%rh_manager = RoutehandleManager()

   end function new_EsmfRegridderFactory

   logical function supports(this, param)
      class(EsmfRegridderFactory), intent(in) :: this
      class(RegridderParam), intent(in) :: param

      type(EsmfRegridderParam) :: reference

      supports = same_type_as(param, reference)
      
   end function supports

   function make_regridder_typesafe(this, spec, rc) result(regriddr)
      class(Regridder), allocatable  :: regriddr
      class(EsmfRegridderFactory), intent(inout) :: this
      type(RegridderSpec), intent(in) :: spec
      integer, optional, intent(out) :: rc

      integer :: status
      type(ESMF_Routehandle) :: routehandle
      type(RoutehandleSpec) :: rh_spec

      regriddr = NULL_REGRIDDER
      associate (p => spec%get_param())
        select type (p)
        type is (EsmfRegridderParam)
!#           routehandle = make_routehandle(spec%get_geom_in(), spec%get_geom_out(), p%get_routehandle_param(), _RC)
           rh_spec = RoutehandleSpec(spec%get_geom_in(), spec%get_geom_out(), p%get_routehandle_param())
           routehandle = this%rh_manager%get_routehandle(rh_spec, _RC)
        class default
           _FAIL('Wrong RegridderParam subclass passed to EsmfRegridderFactory.')
        end select
      end associate
      deallocate(regriddr) ! workaround for gfortran 12.3
      regriddr = EsmfRegridder(routehandle=routehandle, regridder_spec=spec)
      
      _RETURN(_SUCCESS)
   end function make_regridder_typesafe
   
end module mapl3g_EsmfRegridderFactory