MAPL_SetVarSpecForCC Subroutine

public subroutine MAPL_SetVarSpecForCC(GCA, GCB, CCAxB, RC)

Arguments

Type IntentOptional Attributes Name
type(ESMF_GridComp), intent(inout) :: GCA
type(ESMF_GridComp), intent(inout) :: GCB
type(ESMF_CplComp), intent(inout) :: CCAxB
integer, intent(out), optional :: RC

Calls

proc~~mapl_setvarspecforcc~~CallsGraph proc~mapl_setvarspecforcc MAPL_SetVarSpecForCC ESMF_GridCompGet ESMF_GridCompGet proc~mapl_setvarspecforcc->ESMF_GridCompGet interface~mapl_varspecaddreftolist MAPL_VarSpecAddRefToList proc~mapl_setvarspecforcc->interface~mapl_varspecaddreftolist interface~mapl_varspecget MAPL_VarSpecGet proc~mapl_setvarspecforcc->interface~mapl_varspecget interface~mapl_varspecgetindex MAPL_VarSpecGetIndex proc~mapl_setvarspecforcc->interface~mapl_varspecgetindex interface~mapl_varspecprint MAPL_VarSpecPrint proc~mapl_setvarspecforcc->interface~mapl_varspecprint interface~write_parallel WRITE_PARALLEL proc~mapl_setvarspecforcc->interface~write_parallel proc~mapl_cplcompsetvarspecs MAPL_CplCompSetVarSpecs proc~mapl_setvarspecforcc->proc~mapl_cplcompsetvarspecs proc~mapl_internalstateretrieve MAPL_InternalStateRetrieve proc~mapl_setvarspecforcc->proc~mapl_internalstateretrieve proc~mapl_return MAPL_Return proc~mapl_setvarspecforcc->proc~mapl_return proc~mapl_verify MAPL_Verify proc~mapl_setvarspecforcc->proc~mapl_verify proc~mapl_cplcompsetvarspecs->interface~mapl_varspecget proc~mapl_cplcompsetvarspecs->proc~mapl_return proc~mapl_cplcompsetvarspecs->proc~mapl_verify ESMF_CplCompGet ESMF_CplCompGet proc~mapl_cplcompsetvarspecs->ESMF_CplCompGet ESMF_CplCompGetInternalState ESMF_CplCompGetInternalState proc~mapl_cplcompsetvarspecs->ESMF_CplCompGetInternalState interface~mapl_assert MAPL_Assert proc~mapl_cplcompsetvarspecs->interface~mapl_assert proc~mapl_internalstateretrieve->ESMF_GridCompGet proc~mapl_internalstateretrieve->proc~mapl_return proc~mapl_internalstateretrieve->proc~mapl_verify ESMF_UserCompGetInternalState ESMF_UserCompGetInternalState proc~mapl_internalstateretrieve->ESMF_UserCompGetInternalState proc~mapl_internalstatecreate MAPL_InternalStateCreate proc~mapl_internalstateretrieve->proc~mapl_internalstatecreate at at proc~mapl_return->at insert insert proc~mapl_return->insert proc~mapl_throw_exception MAPL_throw_exception proc~mapl_return->proc~mapl_throw_exception proc~mapl_verify->proc~mapl_throw_exception proc~mapl_internalstatecreate->ESMF_GridCompGet proc~mapl_internalstatecreate->proc~mapl_return proc~mapl_internalstatecreate->proc~mapl_verify ESMF_UserCompSetInternalState ESMF_UserCompSetInternalState proc~mapl_internalstatecreate->ESMF_UserCompSetInternalState none~get_component~4 ConcreteComposite%get_component proc~mapl_internalstatecreate->none~get_component~4 none~initialize~19 ConcreteComposite%initialize proc~mapl_internalstatecreate->none~initialize~19 none~set_composite~2 CompositeComponent%set_composite proc~mapl_internalstatecreate->none~set_composite~2

Source Code

   subroutine MAPL_SetVarSpecForCC(gcA, gcB, ccAxB, rc)
      type(ESMF_GridComp), intent(inout) :: GCA
      type(ESMF_GridComp), intent(inout) :: GCB
      type(ESMF_CplComp) , intent(inout) :: CCAxB
      integer, optional,   intent(  out) :: RC     ! Error code:

      ! Local vars
      character(len=ESMF_MAXSTR)   :: NAME
      integer                      :: status
      integer                      :: I, N, STAT
      type (MAPL_VarSpec), pointer :: SRCS(:)
      type (MAPL_VarSpec), pointer :: DSTS(:)
      type (MAPL_VarSpec), pointer :: IM_SPECS(:), EX_SPECS(:)

      ! Begin

      NULLIFY(SRCS)
      NULLIFY(DSTS)

      call MAPL_GridCompGetVarSpecs(gcA, EXPORT=EX_SPECS, RC=status)
      _VERIFY(status)

      call MAPL_GridCompGetVarSpecs(gcB, IMPORT=IM_SPECS,  RC=status)
      _VERIFY(status)

      DO I = 1, size(IM_SPECS)
         call MAPL_VarSpecGet(IM_SPECS(I), STAT=STAT, RC=status)
         _VERIFY(status)

         IF (IAND(STAT, MAPL_BundleItem) /= 0) then
            cycle
         END IF

         call MAPL_VarSpecAddRefToList(DSTS, IM_SPECS(I), RC=status)
         _VERIFY(status)
      END DO

      IF (.not. associated(DSTS)) then
         _RETURN(ESMF_FAILURE)
      END IF

      DO I = 1, size(DSTS)
         call MAPL_VarSpecGet(DSTS(I), STAT=STAT, SHORT_NAME=NAME, RC=status)
         _VERIFY(status)

         N =  MAPL_VarSpecGetIndex(EX_SPECS, NAME, RC=status)
         if(N /= -1) then
            _VERIFY(status)
         else
            call WRITE_PARALLEL("ERROR: cannot match spec:")
            call MAPL_VarSpecPrint(DSTS(I))
            _RETURN(ESMF_FAILURE)
         endif

         call MAPL_VarSpecAddRefToList(SRCS, DSTS(I), RC=status)
         _VERIFY(status)
      END DO

      call MAPL_CplCompSetVarSpecs(ccAxB, SRCS, DSTS, RC=status)
      _VERIFY(status)

      _RETURN(ESMF_SUCCESS)

   end subroutine MAPL_SetVarSpecForCC