get_hconfig.F90 Source File


This file depends on

sourcefile~~get_hconfig.f90~~EfferentGraph sourcefile~get_hconfig.f90 get_hconfig.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~get_hconfig.f90->sourcefile~errorhandling.f90 sourcefile~hconfig_params.f90 hconfig_params.F90 sourcefile~get_hconfig.f90->sourcefile~hconfig_params.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~hconfig_params.f90->sourcefile~errorhandling.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~hconfig_params.f90->sourcefile~pflogger_stub.f90 sourcefile~pfl_keywordenforcer.f90 PFL_KeywordEnforcer.F90 sourcefile~pflogger_stub.f90->sourcefile~pfl_keywordenforcer.f90 sourcefile~wraparray.f90 WrapArray.F90 sourcefile~pflogger_stub.f90->sourcefile~wraparray.f90

Files dependent on this one

sourcefile~~get_hconfig.f90~~AfferentGraph sourcefile~get_hconfig.f90 get_hconfig.F90 sourcefile~hconfig_get_private.f90 hconfig_get_private.F90 sourcefile~hconfig_get_private.f90->sourcefile~get_hconfig.f90 sourcefile~hconfig_get.f90 hconfig_get.F90 sourcefile~hconfig_get.f90->sourcefile~hconfig_get_private.f90 sourcefile~test_hconfig_get_private.pf Test_hconfig_get_private.pf sourcefile~test_hconfig_get_private.pf->sourcefile~hconfig_get_private.f90 sourcefile~hconfig3g.f90 HConfig3G.F90 sourcefile~hconfig3g.f90->sourcefile~hconfig_get.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~mapl_generic.f90~2->sourcefile~hconfig_get.f90 sourcefile~generic3g.f90 Generic3g.F90 sourcefile~generic3g.f90->sourcefile~mapl_generic.f90~2 sourcefile~mapl3_deprecated.f90 MAPL3_Deprecated.F90 sourcefile~mapl3_deprecated.f90->sourcefile~mapl_generic.f90~2 sourcefile~protoextdatagc.f90 ProtoExtDataGC.F90 sourcefile~protoextdatagc.f90->sourcefile~mapl_generic.f90~2 sourcefile~simpleleafgridcomp.f90 SimpleLeafGridComp.F90 sourcefile~simpleleafgridcomp.f90->sourcefile~mapl_generic.f90~2 sourcefile~simpleparentgridcomp.f90 SimpleParentGridComp.F90 sourcefile~simpleparentgridcomp.f90->sourcefile~mapl_generic.f90~2 sourcefile~test_runchild.pf Test_RunChild.pf sourcefile~test_runchild.pf->sourcefile~mapl_generic.f90~2 sourcefile~test_scenarios.pf Test_Scenarios.pf sourcefile~test_scenarios.pf->sourcefile~mapl_generic.f90~2 sourcefile~test_simpleleafgridcomp.pf Test_SimpleLeafGridComp.pf sourcefile~test_simpleleafgridcomp.pf->sourcefile~mapl_generic.f90~2 sourcefile~test_simpleparentgridcomp.pf Test_SimpleParentGridComp.pf sourcefile~test_simpleparentgridcomp.pf->sourcefile~mapl_generic.f90~2

Source Code

#include "MAPL_ErrLog.h"
module mapl3g_get_hconfig

   use mapl3g_hconfig_params
   use :: esmf, only: ESMF_KIND_R4, ESMF_KIND_R8, ESMF_KIND_I4, ESMF_KIND_I8
   use :: esmf, only: ESMF_HConfig, ESMF_HConfigAsString
   use :: esmf, only: ESMF_HConfigAsLogical, ESMF_HConfigAsLogicalSeq
   use :: esmf, only: ESMF_HConfigAsI4, ESMF_HConfigAsI4Seq 
   use :: esmf, only: ESMF_HConfigAsR4, ESMF_HConfigAsR4Seq
   use :: esmf, only: ESMF_HConfigAsI8, ESMF_HConfigAsI8Seq 
   use :: esmf, only: ESMF_HConfigAsR8, ESMF_HConfigAsR8Seq
   use mapl_ErrorHandling

   implicit none
   private

   public :: get_hconfig

   interface get_hconfig
      procedure :: get_hconfig_as_i4
      procedure :: get_hconfig_as_i8
      procedure :: get_hconfig_as_r4
      procedure :: get_hconfig_as_r8
      procedure :: get_hconfig_as_logical
      procedure :: get_hconfig_as_i4seq
      procedure :: get_hconfig_as_i8seq
      procedure :: get_hconfig_as_r4seq
      procedure :: get_hconfig_as_r8seq
      procedure :: get_hconfig_as_logical_seq
      procedure :: get_hconfig_as_string
   end interface get_hconfig

contains

   subroutine get_hconfig_as_i4(value, params, rc)
      integer(kind=ESMF_KIND_I4), intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsI4(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_i4

   subroutine get_hconfig_as_i8(value, params, rc)
      integer(kind=ESMF_KIND_I8), intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsI8(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_i8

   subroutine get_hconfig_as_r4(value, params, rc)
      real(kind=ESMF_KIND_R4), intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsR4(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_r4
   
   subroutine get_hconfig_as_r8(value, params, rc)
      real(kind=ESMF_KIND_R8), intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsR8(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_r8

   subroutine get_hconfig_as_logical(value, params, rc)
      logical, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsLogical(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_logical

   subroutine get_hconfig_as_string(value, params, rc)
      character(len=:), allocatable, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsString(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_string

   subroutine get_hconfig_as_i4seq(value, params, rc)
      integer(kind=ESMF_KIND_I4), dimension(:), allocatable, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsI4Seq(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_i4seq

   subroutine get_hconfig_as_i8seq(value, params, rc)
      integer(kind=ESMF_KIND_I8), dimension(:), allocatable, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsI8Seq(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_i8seq

   subroutine get_hconfig_as_r4seq(value, params, rc)
      real(kind=ESMF_KIND_R4), dimension(:), allocatable, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsR4Seq(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_r4seq
   
   subroutine get_hconfig_as_r8seq(value, params, rc)
      real(kind=ESMF_KIND_R8), dimension(:), allocatable, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsR8Seq(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_r8seq

   subroutine get_hconfig_as_logical_seq(value, params, rc)
      logical, dimension(:), allocatable, intent(out) :: value
      class(HConfigParams), intent(in) :: params
      integer, optional, intent(out) :: rc
      integer :: status

      value = ESMF_HConfigAsLogicalSeq(params%hconfig, keyString=params%label, _RC)
      _RETURN(_SUCCESS)

   end subroutine get_hconfig_as_logical_seq

end module mapl3g_get_hconfig