RegridMethods.F90 Source File


Files dependent on this one

sourcefile~~regridmethods.f90~~AfferentGraph sourcefile~regridmethods.f90 RegridMethods.F90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~regridmethods.f90 sourcefile~extdatagridcompmod.f90 ExtDataGridCompMod.F90 sourcefile~extdatagridcompmod.f90->sourcefile~regridmethods.f90 sourcefile~extdataoldtypescreator.f90 ExtDataOldTypesCreator.F90 sourcefile~extdataoldtypescreator.f90->sourcefile~regridmethods.f90 sourcefile~fieldbundleread.f90 FieldBundleRead.F90 sourcefile~fieldbundleread.f90->sourcefile~regridmethods.f90 sourcefile~griddedio.f90 GriddedIO.F90 sourcefile~griddedio.f90->sourcefile~regridmethods.f90 sourcefile~horizontalfluxregridder.f90 HorizontalFluxRegridder.F90 sourcefile~horizontalfluxregridder.f90->sourcefile~regridmethods.f90 sourcefile~mapl_cfio.f90 MAPL_CFIO.F90 sourcefile~mapl_cfio.f90->sourcefile~regridmethods.f90 sourcefile~mapl_epochswathmod.f90 MAPL_EpochSwathMod.F90 sourcefile~mapl_epochswathmod.f90->sourcefile~regridmethods.f90 sourcefile~mapl_esmfregridder.f90 MAPL_EsmfRegridder.F90 sourcefile~mapl_esmfregridder.f90->sourcefile~regridmethods.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~regridmethods.f90 sourcefile~mapl_identityregridder.f90 MAPL_IdentityRegridder.F90 sourcefile~mapl_identityregridder.f90->sourcefile~regridmethods.f90 sourcefile~mapl_latlontolatlonregridder.f90 MAPL_LatLonToLatLonRegridder.F90 sourcefile~mapl_latlontolatlonregridder.f90->sourcefile~regridmethods.f90 sourcefile~mapl_regriddermanager.f90 MAPL_RegridderManager.F90 sourcefile~mapl_regriddermanager.f90->sourcefile~regridmethods.f90 sourcefile~mapl_tilingregridder.f90 MAPL_TilingRegridder.F90 sourcefile~mapl_tilingregridder.f90->sourcefile~regridmethods.f90 sourcefile~mapl_transposeregridder.f90 MAPL_TransposeRegridder.F90 sourcefile~mapl_transposeregridder.f90->sourcefile~regridmethods.f90 sourcefile~newregriddermanager.f90 NewRegridderManager.F90 sourcefile~newregriddermanager.f90->sourcefile~regridmethods.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~regridmethods.f90 sourcefile~regridderspec.f90 RegridderSpec.F90 sourcefile~regridderspec.f90->sourcefile~regridmethods.f90 sourcefile~regriddertypespec.f90 RegridderTypeSpec.F90 sourcefile~regriddertypespec.f90->sourcefile~regridmethods.f90

Source Code

module mapl_RegridMethods
   use ESMF
   implicit none
   private

   public :: REGRID_HINT_LOCAL
   public :: REGRID_HINT_FILE_WEIGHTS
   public :: REGRID_HINT_COMPUTE_TRANSPOSE
   public :: REGRID_METHOD_IDENTITY
   public :: REGRID_METHOD_BILINEAR
   public :: REGRID_METHOD_BILINEAR_MONOTONIC
   public :: REGRID_METHOD_BILINEAR_ROTATE
   public :: REGRID_METHOD_CONSERVE
   public :: REGRID_METHOD_CONSERVE_MONOTONIC
   public :: REGRID_METHOD_VOTE
   public :: REGRID_METHOD_FRACTION
   public :: REGRID_METHOD_CONSERVE_2ND
   public :: REGRID_METHOD_PATCH
   public :: REGRID_METHOD_NEAREST_STOD
   public :: REGRID_METHOD_CONSERVE_HFLUX
   public :: UNSPECIFIED_REGRID_METHOD
   public :: TILING_METHODS
   public :: regrid_method_string_to_int
   public :: regrid_method_int_to_string

   enum, bind(c)
      enumerator :: REGRID_METHOD_IDENTITY
      enumerator :: REGRID_METHOD_BILINEAR
      enumerator :: REGRID_METHOD_BILINEAR_ROTATE
      enumerator :: REGRID_METHOD_CONSERVE
      enumerator :: REGRID_METHOD_VOTE
      enumerator :: REGRID_METHOD_FRACTION
      enumerator :: REGRID_METHOD_CONSERVE_2ND
      enumerator :: REGRID_METHOD_PATCH
      enumerator :: REGRID_METHOD_NEAREST_STOD
      enumerator :: REGRID_METHOD_CONSERVE_HFLUX
      enumerator :: REGRID_METHOD_BILINEAR_MONOTONIC
      enumerator :: REGRID_METHOD_CONSERVE_MONOTONIC
      enumerator :: UNSPECIFIED_REGRID_METHOD = -1
   end enum
   integer, parameter :: TILING_METHODS(3) = [REGRID_METHOD_CONSERVE,REGRID_METHOD_VOTE,REGRID_METHOD_FRACTION]
   integer, parameter :: REGRID_HINT_LOCAL = 1
   integer, parameter :: REGRID_HINT_FILE_WEIGHTS = 2
   integer, parameter :: REGRID_HINT_COMPUTE_TRANSPOSE = 4

   contains

   function regrid_method_string_to_int(string_regrid_method) result(int_regrid_method)
      integer :: int_regrid_method
      character(len=*), intent(in) :: string_regrid_method

      character(len=:), allocatable :: temp_str
      temp_str = ESMF_UtilStringUpperCase(trim(string_regrid_method))

      select case (temp_str)
      case ("IDENTITY")
         int_regrid_method = REGRID_METHOD_IDENTITY
      case ("BILINEAR")
         int_regrid_method = REGRID_METHOD_BILINEAR
      case ("BILINEAR_ROTATE")
         int_regrid_method = REGRID_METHOD_BILINEAR_ROTATE
      case ("CONSERVE")
         int_regrid_method = REGRID_METHOD_CONSERVE
      case ("VOTE")
         int_regrid_method = REGRID_METHOD_VOTE
      case ("FRACTION")
         int_regrid_method = REGRID_METHOD_FRACTION
      case ("CONSERVE_2ND")
         int_regrid_method = REGRID_METHOD_CONSERVE_2ND
      case ("PATCH")
         int_regrid_method = REGRID_METHOD_PATCH
      case ("CONSERVE_HFLUX")
         int_regrid_method = REGRID_METHOD_CONSERVE_HFLUX
      case ("CONSERVE_MONOTONIC")
         int_regrid_method = REGRID_METHOD_CONSERVE_MONOTONIC
      case ("BILINEAR_MONOTONIC")
         int_regrid_method = REGRID_METHOD_BILINEAR_MONOTONIC
      case ("NEAREST_STOD")
         int_regrid_method = REGRID_METHOD_NEAREST_STOD
      case default
         int_regrid_method = UNSPECIFIED_REGRID_METHOD
      end select
   end function

   function regrid_method_int_to_string(int_regrid_method) result(string_regrid_method)
      integer, intent(in) :: int_regrid_method
      character(len=:), allocatable :: string_regrid_method

      select case (int_regrid_method)
      case (REGRID_METHOD_IDENTITY)
         string_regrid_method = "identity"
      case (REGRID_METHOD_BILINEAR)
         string_regrid_method = "bilinear"
      case (REGRID_METHOD_BILINEAR_ROTATE)
         string_regrid_method = "bilinear_rotate"
      case (REGRID_METHOD_CONSERVE)
         string_regrid_method = "conserve"
      case (REGRID_METHOD_VOTE)
         string_regrid_method = "vote"
      case (REGRID_METHOD_FRACTION)
         string_regrid_method = "fraction"
      case (REGRID_METHOD_CONSERVE_2ND)
         string_regrid_method = "conserve_2nd"
      case (REGRID_METHOD_PATCH)
         string_regrid_method = "patch"
      case (REGRID_METHOD_CONSERVE_HFLUX)
         string_regrid_method = "conserve_hflux"
      case (REGRID_METHOD_CONSERVE_MONOTONIC)
         string_regrid_method = "conserve_monotonic"
      case (REGRID_METHOD_BILINEAR_MONOTONIC)
         string_regrid_method = "bilinear_monotonic"
      case (REGRID_METHOD_NEAREST_STOD)
         string_regrid_method = "nearest_stod"
      case default
         string_regrid_method = "unspecified_regrid_method"
      end select
   end function
end module mapl_RegridMethods