recursive subroutine ESMF_CompGet(compp, name, vm, vm_parent, vmplan, &
    vm_info, contextflag, grid, gridList, mesh, meshList, locstream, &
    locstreamList, xgrid, xgridList, importState, exportState, clock, dirPath, &
    configFile, config, hconfig, compType, currentMethod, currentPhase, &
    timeout, localPet, petCount, petList, compStatus, compTunnel, rc)
!
! !ARGUMENTS:
    type(ESMF_CompClass),     pointer               :: compp
    character(len=*),         intent(out), optional :: name
    type(ESMF_VM),            intent(out), optional :: vm
    type(ESMF_VM),            intent(out), optional :: vm_parent
    type(ESMF_VMPlan),        intent(out), optional :: vmplan
    type(ESMF_Pointer),       intent(out), optional :: vm_info
    type(ESMF_Context_Flag),  intent(out), optional :: contextflag
    type(ESMF_Grid),          intent(out), optional :: grid
    type(ESMF_Grid), allocatable, intent(out), optional :: gridList(:)
    type(ESMF_Mesh),          intent(out), optional :: mesh
    type(ESMF_Mesh), allocatable, intent(out), optional :: meshList(:)
    type(ESMF_LocStream),     intent(out), optional :: locstream
    type(ESMF_LocStream), allocatable, intent(out), optional :: locstreamList(:)
    type(ESMF_XGrid),         intent(out), optional :: xgrid
    type(ESMF_XGrid), allocatable, intent(out), optional :: xgridList(:)
    type(ESMF_State),         intent(out), optional :: importState
    type(ESMF_State),         intent(out), optional :: exportState
    type(ESMF_Clock),         intent(out), optional :: clock
    character(len=*),         intent(out), optional :: dirPath
    character(len=*),         intent(out), optional :: configFile
    type(ESMF_Config),        intent(out), optional :: config
    type(ESMF_HConfig),       intent(out), optional :: hconfig
    type(ESMF_CompType_Flag), intent(out), optional :: compType
    type(ESMF_Method_Flag),   intent(out), optional :: currentMethod
    integer,                  intent(out), optional :: currentPhase
    integer,                  intent(out), optional :: timeout
    integer,                  intent(out), optional :: localPet
    integer,                  intent(out), optional :: petCount
    integer,                  pointer,     optional :: petList(:)
    type(ESMF_CompStatus),    intent(out), optional :: compStatus
    type(ESMF_CompTunnel),    intent(out), optional :: compTunnel
    integer,                  intent(out), optional :: rc
!
! !DESCRIPTION:
!      Returns information about the component.
!
!EOPI
!------------------------------------------------------------------------------
    integer                 :: localrc, stat      ! local return code
    type(ESMF_Status)       :: baseStatus
    type(ESMF_Method_Flag)  :: currentMethodArg
    integer                 :: currentPhaseArg
    integer                 :: timeoutArg
    ! Initialize return code; assume not implemented until success is certain
    localrc = ESMF_RC_NOT_IMPL
    if (present(rc)) rc = ESMF_RC_NOT_IMPL
        
    ! Test incoming compp object
    if (.not.associated(compp)) then
      call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
        msg="Not a valid pointer to ESMF Component object", &
        ESMF_CONTEXT, rcToReturn=rc)
      return
    endif
    ! Check init status of arguments
    ESMF_INIT_CHECK_DEEP(ESMF_CompClassGetInit, compp, rc)
    call ESMF_BaseGetStatus(compp%base, baseStatus, rc=localrc)
    if (ESMF_LogFoundError(localrc, &
        ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
        
    if (baseStatus /= ESMF_STATUS_READY) then
      call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
        msg="uninitialized or destroyed Component object.", &
        ESMF_CONTEXT, rcToReturn=rc)
      return  ! bail out
    endif
    ! access grid
    if (present(grid)) then
      if (.not.compp%compStatus%gridIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested Grid object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      grid = compp%gridList(1)  ! return first element
    endif
    if (present(gridList)) then
      if (allocated(gridList)) deallocate(gridList) ! deallocate incoming
      allocate(gridList(size(compp%gridList)))      ! allocate to correct size
      gridList(:) = compp%gridList(:)               ! copy entries
    endif
    ! access mesh
    if (present(mesh)) then
      if (.not.compp%compStatus%meshIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested Mesh object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      mesh = compp%meshList(1)  ! return first element
    endif
    if (present(meshList)) then
      if (allocated(meshList)) deallocate(meshList) ! deallocate incoming
      allocate(meshList(size(compp%meshList)))      ! allocate to correct size
      meshList(:) = compp%meshList(:)               ! copy entries
    endif
    ! access locstream
    if (present(locstream)) then
      if (.not.compp%compStatus%locstreamIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested locstream object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      locstream = compp%locstreamList(1)  ! return first element
    endif
    if (present(locstreamList)) then
      if (allocated(locstreamList)) deallocate(locstreamList) ! deallocate incoming
      allocate(locstreamList(size(compp%locstreamList)))      ! allocate to correct size
      locstreamList(:) = compp%locstreamList(:)               ! copy entries
    endif
    ! access xgrid
    if (present(xgrid)) then
      if (.not.compp%compStatus%xgridIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested xgrid object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      xgrid = compp%xgridList(1)  ! return first element
    endif
    if (present(xgridList)) then
      if (allocated(xgridList)) deallocate(xgridList) ! deallocate incoming
      allocate(xgridList(size(compp%xgridList)))      ! allocate to correct size
      xgridList(:) = compp%xgridList(:)               ! copy entries
    endif
    ! access config
    if (present(config)) then
      if (.not.compp%compStatus%configIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested Config object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      config = compp%config
    endif
    ! access hconfig
    if (present(hconfig)) then
      if (.not.compp%compStatus%configIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested HConfig object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      call ESMF_ConfigGet(compp%config, hconfig=hconfig, rc=localrc)
      if (ESMF_LogFoundError(localrc, &
        ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    ! access name
    if (present(name)) then
      call ESMF_GetName(compp%base, name, rc=localrc)
      if (ESMF_LogFoundError(localrc, &
        ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    ! access compType
    if (present(compType)) then
      compType = compp%compType
    endif
    ! access vm
    if (present(vm)) then
      if (.not.compp%compStatus%vmIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested VM object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      vm = compp%vm
    endif
    ! access vm_parent
    if (present(vm_parent)) then
      vm_parent = compp%vm_parent
    endif
    ! access vmplan
    if (present(vmplan)) then
      vmplan = compp%vmplan
    endif
    ! access vm_info
    if (present(vm_info)) then
      vm_info = compp%vm_info
    endif
    ! access contextflag
    if (present(contextflag)) then
      contextflag = compp%contextflag
    endif
    ! access importState
    if (present(importState)) then
      if (.not.compp%compStatus%isIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested importState object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      importState = compp%is
    endif
    ! access exportState
    if (present(exportState)) then
      if (.not.compp%compStatus%esIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested exportState object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      exportState = compp%es
    endif
    ! access clock
    if (present(clock)) then
      if (.not.compp%compStatus%clockIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested Clock object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      clock = compp%clock
    endif
    ! access dirPath
    if (present(dirPath)) then
      dirPath = compp%dirPath
    endif
    ! access configFile
    if (present(configFile)) then
      if (.not.compp%compStatus%configFileIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="requested configFile object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      configFile = compp%configFile
    endif
    ! access currentMethod, currentPhase, timeout
    if (present(currentMethod) &
      .or. present(currentPhase) &
      .or. present(timeout)) then
      call c_ESMC_CompGet(compp%vm_cargo, currentMethodArg, currentPhaseArg, &
        timeoutArg, localrc)
      if (ESMF_LogFoundError(localrc, &
        ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    if (present(currentMethod)) then
      currentMethod = currentMethodArg
    endif
    if (present(currentPhase)) then
      currentPhase = currentPhaseArg
    endif
    if (present(timeout)) then
      timeout = timeoutArg
    endif
    ! access localPet
    if (present(localPet)) then
      if (.not.compp%compStatus%vmIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="VM object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      call ESMF_VMGet(compp%vm, localPet=localPet, rc=localrc)
      if (ESMF_LogFoundError(localrc, &
        ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    ! access petCount
    if (present(petCount)) then
      if (.not.compp%compStatus%vmIsPresent) then
        call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
          msg="VM object is not present.", &
          ESMF_CONTEXT, rcToReturn=rc)
        return  ! bail out
      endif
      call ESMF_VMGet(compp%vm, petCount=petCount, rc=localrc)
      if (ESMF_LogFoundError(localrc, &
        ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    ! access petList
    if (present(petList)) then
      if (associated(petList)) then
        if (size(petList) /= compp%npetlist) then
          call ESMF_LogSetError(ESMF_RC_OBJ_BAD, &
            msg="- size of provided petList argument does not match.", &
            ESMF_CONTEXT, rcToReturn=rc)
          return  ! bail out
        endif
      else
        allocate(petlist(compp%npetlist), stat=stat)
        if (ESMF_LogFoundAllocError(stat, msg="local petlist", &
          ESMF_CONTEXT, rcToReturn=rc)) return 
      endif
      petList = compp%petList ! copy the petList content
    endif
    ! access compStatus
    if (present(compStatus)) then
      compStatus = compp%compStatus
    endif
    ! access compTunnel
    if (present(compTunnel)) then
      compTunnel = compp%compTunnel
    endif
    ! Return successfully
    if (present(rc)) rc = ESMF_SUCCESS
  end subroutine ESMF_CompGet