ESMF_ConfigGetIntI4 Subroutine

private subroutine ESMF_ConfigGetIntI4(config, value, keywordEnforcer, label, default, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Config), intent(inout) :: config
integer(kind=ESMF_KIND_I4), intent(out) :: value
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
character(len=*), intent(in), optional :: label
integer(kind=ESMF_KIND_I4), intent(in), optional :: default
integer, intent(out), optional :: rc

Source Code

      subroutine ESMF_ConfigGetIntI4(config, value, &
        keywordEnforcer, label, default, rc)

! !ARGUMENTS:
      type(ESMF_Config), intent(inout)            :: config
      integer(ESMF_KIND_I4), intent(out)          :: value
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
      character(len=*), intent(in), optional      :: label
      integer(ESMF_KIND_I4), intent(in), optional :: default
      integer, intent(out), optional              :: rc

!
! !DESCRIPTION: 
!  Gets an integer {\tt value} from the {\tt config} object.
!
!   The arguments are:
!   \begin{description}
!   \item [config]
!     Already created {\tt ESMF\_Config} object.
!   \item [value]
!     Returned integer value. 
!   \item [{[label]}]
!     Identifying label. 
!   \item [{[default]}]
!     Default value if label is not found in configuration object. 
!   \item [{[rc]}]
!     Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!   \end{description}
!
!EOPI -------------------------------------------------------------------

      integer :: localrc
      character(len=LSZ) :: string
      real(ESMF_KIND_R8) :: x
      integer(ESMF_KIND_I4) ::  n
      integer :: iostat

      ! Initialize return code; assume routine not implemented
      if (present(rc)) rc = ESMF_RC_NOT_IMPL

      localrc = ESMF_SUCCESS
      !check variables
      ESMF_INIT_CHECK_DEEP(ESMF_ConfigGetInit,config,rc)

! Default setting
      if( present( default ) ) then 
         value = default
      else
         value = 0
      endif

! Processing
      if (present (label ) ) then
         call ESMF_ConfigGetString( config, string, label=label, rc=localrc)
      else
         call ESMF_ConfigGetString( config, string, rc = localrc )
      endif

      if ( localrc == ESMF_SUCCESS ) then
           read(string,*,iostat=iostat) x
           if ( iostat == 0 ) then
             call ESMF_ConfigSetCurrentAttrUsed(config, used=.true.)
           else
             ! undo what GetSring() did
             call ESMF_ConfigSetCurrentAttrUsed(config, used=.false.)
             localrc = ESMF_RC_VAL_OUTOFRANGE
           endif
      end if
      if ( localrc == ESMF_SUCCESS ) then
         n = nint(x)
      else
         if( present( default )) then
            n = default
            localrc = ESMF_SUCCESS
         else
            n = 0
         endif
      endif

      if ( localrc == ESMF_SUCCESS ) then
         value = n
      endif

      if( present( rc )) then
        rc = localrc
      endif
      
    end subroutine ESMF_ConfigGetIntI4