ESMF_FieldSMMStoreFromFile Subroutine

private subroutine ESMF_FieldSMMStoreFromFile(srcField, dstField, filename, routehandle, keywordEnforcer, ignoreUnmatchedIndices, srcTermProcessing, pipeLineDepth, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Field), intent(in) :: srcField
type(ESMF_Field), intent(inout) :: dstField
character(len=*), intent(in) :: filename
type(ESMF_RouteHandle), intent(inout) :: routehandle
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
logical, intent(in), optional :: ignoreUnmatchedIndices
integer, intent(inout), optional :: srcTermProcessing
integer, intent(inout), optional :: pipeLineDepth
integer, intent(out), optional :: rc

Source Code

    subroutine ESMF_FieldSMMStoreFromFile(srcField, dstField, filename, &
      routehandle, keywordEnforcer, ignoreUnmatchedIndices, &
      srcTermProcessing, pipelineDepth, rc)

! ! ARGUMENTS:
      type(ESMF_Field),       intent(in)              :: srcField  
      type(ESMF_Field),       intent(inout)           :: dstField
      character(len=*),       intent(in)              :: filename
      type(ESMF_RouteHandle), intent(inout)           :: routehandle
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
      logical,                intent(in),    optional :: ignoreUnmatchedIndices
      integer,                intent(inout), optional :: srcTermProcessing
      integer,                intent(inout), optional :: pipeLineDepth
      integer,                intent(out),   optional :: rc
!
! !DESCRIPTION:
!
! Compute an {\tt ESMF\_RouteHandle} using factors read from file.
!
! The arguments are:
!
! \begin{description}
!
! \item [srcField]
!       {\tt ESMF\_Field} with source data.
!
! \item [dstField]
!       {\tt ESMF\_Field} with destination data. The data in this Field may be
!       destroyed by this call.
!
! \item [filename]
!       Path to the file containing weights for creating an {\tt ESMF\_RouteHandle}.
!       See ~(\ref{sec:weightfileformat}) for a description of the SCRIP weight
!       file format. Only "row", "col", and "S" variables are required. They
!       must be one-dimensionsal with dimension "n\_s".
!
! \item [routehandle]
!       Handle to the {\tt ESMF\_RouteHandle}.
!
!   \item [{[ignoreUnmatchedIndices]}]
!     A logical flag that affects the behavior for when sequence indices
!     in the sparse matrix are encountered that do not have a match on the
!     {\tt srcField} or {\tt dstField} side. The default setting is
!     {\tt .false.}, indicating that it is an error when such a situation is
!     encountered. Setting {\tt ignoreUnmatchedIndices} to {\tt .true.} ignores
!     entries with unmatched indices.
!
!   \item [{[srcTermProcessing]}]
!     The {\tt srcTermProcessing} parameter controls how many source terms,
!     located on the same PET and summing into the same destination element,
!     are summed into partial sums on the source PET before being transferred
!     to the destination PET. A value of 0 indicates that the entire arithmetic
!     is done on the destination PET; source elements are neither multiplied
!     by their factors nor added into partial sums before being sent off by the
!     source PET. A value of 1 indicates that source elements are multiplied
!     by their factors on the source side before being sent to the destination
!     PET. Larger values of {\tt srcTermProcessing} indicate the maximum number
!     of terms in the partial sums on the source side.
!
!     Note that partial sums may lead to bit-for-bit differences in the results.
!     See section \ref{RH:bfb} for an in-depth discussion of {\em all}
!     bit-for-bit reproducibility aspects related to route-based communication
!     methods.
!
!     \begin{sloppypar}
!     The {\tt ESMF\_FieldSMMStore()} method implements an auto-tuning scheme
!     for the {\tt srcTermProcessing} parameter. The intent on the
!     {\tt srcTermProcessing} argument is "{\tt inout}" in order to
!     support both overriding and accessing the auto-tuning parameter.
!     If an argument $>= 0$ is specified, it is used for the
!     {\tt srcTermProcessing} parameter, and the auto-tuning phase is skipped.
!     In this case the {\tt srcTermProcessing} argument is not modified on
!     return. If the provided argument is $< 0$, the {\tt srcTermProcessing}
!     parameter is determined internally using the auto-tuning scheme. In this
!     case the {\tt srcTermProcessing} argument is re-set to the internally
!     determined value on return. Auto-tuning is also used if the optional
!     {\tt srcTermProcessing} argument is omitted.
!     \end{sloppypar}
!
!   \item [{[pipelineDepth]}]
!     The {\tt pipelineDepth} parameter controls how many messages a PET
!     may have outstanding during a sparse matrix exchange. Larger values
!     of {\tt pipelineDepth} typically lead to better performance. However,
!     on some systems too large a value may lead to performance degradation,
!     or runtime errors.
!
!     Note that the pipeline depth has no effect on the bit-for-bit
!     reproducibility of the results. However, it may affect the performance
!     reproducibility of the exchange.
!     The {\tt ESMF\_FieldSMMStore()} method implements an auto-tuning scheme
!     for the {\tt pipelineDepth} parameter. The intent on the
!     {\tt pipelineDepth} argument is "{\tt inout}" in order to
!     support both overriding and accessing the auto-tuning parameter.
!     If an argument $>= 0$ is specified, it is used for the
!     {\tt pipelineDepth} parameter, and the auto-tuning phase is skipped.
!     In this case the {\tt pipelineDepth} argument is not modified on
!     return. If the provided argument is $< 0$, the {\tt pipelineDepth}
!     parameter is determined internally using the auto-tuning scheme. In this
!     case the {\tt pipelineDepth} argument is re-set to the internally
!     determined value on return. Auto-tuning is also used if the optional
!     {\tt pipelineDepth} argument is omitted.
!
!   \item [{[rc]}]
!     Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!
! \end{description}
!
!EOP
!-------------------------------------------------------------------------------

      ! LOCAL VARIABLES:
      real(ESMF_KIND_R8), dimension(:), allocatable :: factorList
      integer, dimension(:, :), allocatable :: factorIndexList
      integer :: localrc

      real(ESMF_KIND_R8), pointer :: src(:,:)

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

      ! Fill the factorList and factorIndexList.
      call ESMF_FactorRead(filename, &
                           factorList, &
                           factorIndexList, &
                           rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

      ! Generate routeHandle from factorList and factorIndexList
      call ESMF_FieldSMMStore(srcField=srcField, &
                              dstField=dstField, &
                              routehandle=routeHandle, &
                              factorList=factorList, &
                              factorIndexList=factorIndexList,   &
                              ignoreUnmatchedIndices=ignoreUnmatchedIndices, &
                              srcTermProcessing=srcTermProcessing, &
                              pipeLineDepth=pipeLineDepth, &
                              rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

      deallocate(factorList)
      deallocate(factorIndexList)

      if (present(rc)) rc = ESMF_SUCCESS

    end subroutine ESMF_FieldSMMStoreFromFile