RegridderTypeSpec.F90 Source File


This file depends on

sourcefile~~regriddertypespec.f90~~EfferentGraph sourcefile~regriddertypespec.f90 RegridderTypeSpec.F90 sourcefile~constants.f90 Constants.F90 sourcefile~regriddertypespec.f90->sourcefile~constants.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~regriddertypespec.f90->sourcefile~keywordenforcer.f90 sourcefile~regridmethods.f90 RegridMethods.F90 sourcefile~regriddertypespec.f90->sourcefile~regridmethods.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~physicalconstants.f90->sourcefile~mathconstants.f90

Files dependent on this one

sourcefile~~regriddertypespec.f90~~AfferentGraph sourcefile~regriddertypespec.f90 RegridderTypeSpec.F90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~regriddertypespec.f90 sourcefile~mapl_regriddermanager.f90 MAPL_RegridderManager.F90 sourcefile~base.f90->sourcefile~mapl_regriddermanager.f90 sourcefile~mapl_regriddermanager.f90->sourcefile~regriddertypespec.f90 sourcefile~mapl_regriddertypespecregriddermap.f90 MAPL_RegridderTypeSpecRegridderMap.F90 sourcefile~mapl_regriddermanager.f90->sourcefile~mapl_regriddertypespecregriddermap.f90 sourcefile~mapl_regriddertypespecregriddermap.f90->sourcefile~regriddertypespec.f90 sourcefile~cubedspheregeomspec_smod.f90 CubedSphereGeomSpec_smod.F90 sourcefile~cubedspheregeomspec_smod.f90->sourcefile~base.f90 sourcefile~equal_to.f90~2 equal_to.F90 sourcefile~equal_to.f90~2->sourcefile~base.f90 sourcefile~make_decomposition.f90 make_decomposition.F90 sourcefile~make_decomposition.f90->sourcefile~base.f90 sourcefile~make_distribution.f90 make_distribution.F90 sourcefile~make_distribution.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_hconfig.f90 make_LatLonGeomSpec_from_hconfig.F90 sourcefile~make_latlongeomspec_from_hconfig.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_metadata.f90 make_LatLonGeomSpec_from_metadata.F90 sourcefile~make_latlongeomspec_from_metadata.f90->sourcefile~base.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~base.f90 sourcefile~mapl_cfio.f90 MAPL_CFIO.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_regriddermanager.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~base.f90 sourcefile~supports_hconfig.f90~2 supports_hconfig.F90 sourcefile~supports_hconfig.f90~2->sourcefile~base.f90 sourcefile~supports_metadata.f90~2 supports_metadata.F90 sourcefile~supports_metadata.f90~2->sourcefile~base.f90 sourcefile~test_cfio_bundle.pf Test_CFIO_Bundle.pf sourcefile~test_cfio_bundle.pf->sourcefile~base.f90 sourcefile~tstqsat.f90 tstqsat.F90 sourcefile~tstqsat.f90->sourcefile~base.f90 sourcefile~ut_extdata.f90 ut_ExtData.F90 sourcefile~ut_extdata.f90->sourcefile~base.f90 sourcefile~utcfio_bundle.f90 utCFIO_Bundle.F90 sourcefile~utcfio_bundle.f90->sourcefile~base.f90

Source Code

#include "MAPL_Generic.h"
! A RegridderSpec is used to indicate which subclass of regridder will be used.
module mapl_RegridderTypeSpec
   use MAPL_Constants
   use MAPL_KeywordEnforcerMod
   use mapl_RegridMethods
   use ESMF
   use, intrinsic :: iso_fortran_env, only: INT64
   implicit none
   private

   public :: RegridderTypeSpec 

   type :: RegridderTypeSpec
      character(len=:), allocatable :: grid_type_in
      character(len=:), allocatable :: grid_type_out
      integer :: regrid_method = UNSPECIFIED_REGRID_METHOD
   contains
      procedure :: less_than
      generic :: operator (<) => less_Than
   end type RegridderTypeSpec

   interface RegridderTypeSpec
      module procedure new_RegridderTypeSpec
   end interface RegridderTypeSpec


contains


   function new_RegridderTypeSpec(grid_type_in, grid_type_out, regrid_method, unusable, rc) result(spec)
      type (RegridderTypeSpec) :: spec
      character(len=*), intent(in) :: grid_type_in
      character(len=*), intent(in) :: grid_type_out
      integer, intent(in) :: regrid_method
      class (KeywordEnforcer), optional, intent(in) :: unusable
      integer, optional, intent(out) :: rc

      _UNUSED_DUMMY(unusable)
      _UNUSED_DUMMY(rc)

      spec%grid_type_in = grid_type_in
      spec%grid_type_out = grid_type_out
      spec%regrid_method = regrid_method

   end function new_RegridderTypeSpec

   logical function less_than(a, b)
      class (RegridderTypeSpec), intent(in) :: a
      type (RegridderTypeSpec), intent(in) :: b

      ! Compare methods

      if (a%regrid_method /= b%regrid_method) then
         less_than = (a%regrid_method < b%regrid_method) ! strictly less than
         return
      end if ! else tie
         
      ! To get here, methods are the same for a and b.
      if (any(a%regrid_method == TILING_METHODS)) then
         less_than = .false.
         ! do not care about grid types in this case
         return
      end if

      ! Compare grid types
      if (a%grid_type_in /= b%grid_type_in) then
         less_than = (a%grid_type_in < b%grid_type_in) ! strictly less than
         return
      end if ! else tie

      ! Compare out grid types
      less_than = (a%grid_type_out < b%grid_type_out)
      return
      
   end function less_than


end module mapl_RegridderTypeSpec
#undef _UNUSED_DUMMY