IOCompUTestCompare Subroutine

subroutine IOCompUTestCompare(inputFields, outputFields, maxdiffI4, maxdiffR4, maxdiffR8, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Field), intent(in), dimension(:) :: inputFields
type(ESMF_Field), intent(in), dimension(:) :: outputFields
integer(kind=ESMF_KIND_I4), intent(out), dimension(:) :: maxdiffI4
real(kind=ESMF_KIND_R4), intent(out), dimension(:) :: maxdiffR4
real(kind=ESMF_KIND_R8), intent(out), dimension(:) :: maxdiffR8
integer, intent(out) :: rc

Calls

proc~~iocomputestcompare~~CallsGraph proc~iocomputestcompare IOCompUTestCompare esmf_fieldget esmf_fieldget proc~iocomputestcompare->esmf_fieldget proc~esmf_logfounderror ESMF_LogFoundError proc~iocomputestcompare->proc~esmf_logfounderror proc~esmf_logseterror ESMF_LogSetError proc~iocomputestcompare->proc~esmf_logseterror esmf_breakpoint esmf_breakpoint proc~esmf_logfounderror->esmf_breakpoint proc~esmf_logrc2msg ESMF_LogRc2Msg proc~esmf_logfounderror->proc~esmf_logrc2msg proc~esmf_logwrite ESMF_LogWrite proc~esmf_logfounderror->proc~esmf_logwrite proc~esmf_logseterror->esmf_breakpoint proc~esmf_logseterror->proc~esmf_logrc2msg proc~esmf_logseterror->proc~esmf_logwrite c_esmc_loggeterrormsg c_esmc_loggeterrormsg proc~esmf_logrc2msg->c_esmc_loggeterrormsg c_esmc_vmwtime c_esmc_vmwtime proc~esmf_logwrite->c_esmc_vmwtime proc~esmf_logclose ESMF_LogClose proc~esmf_logwrite->proc~esmf_logclose proc~esmf_logflush ESMF_LogFlush proc~esmf_logwrite->proc~esmf_logflush proc~esmf_logopenfile ESMF_LogOpenFile proc~esmf_logwrite->proc~esmf_logopenfile proc~esmf_utiliounitflush ESMF_UtilIOUnitFlush proc~esmf_logwrite->proc~esmf_utiliounitflush proc~esmf_utilstring2array ESMF_UtilString2Array proc~esmf_logwrite->proc~esmf_utilstring2array proc~esmf_logclose->proc~esmf_logflush proc~esmf_logflush->proc~esmf_utiliounitflush proc~esmf_utilarray2string ESMF_UtilArray2String proc~esmf_logflush->proc~esmf_utilarray2string proc~esmf_logopenfile->proc~esmf_utiliounitflush proc~esmf_utiliounitget ESMF_UtilIOUnitGet proc~esmf_logopenfile->proc~esmf_utiliounitget

Source Code

  subroutine IOCompUTestCompare(inputFields, outputFields, maxdiffI4, maxdiffR4, maxdiffR8, rc)

    type(ESMF_Field),      dimension(:), intent(in)  :: inputFields, outputFields
    integer(ESMF_KIND_I4), dimension(:), intent(out) :: maxdiffI4
    real   (ESMF_KIND_R4), dimension(:), intent(out) :: maxdiffR4
    real   (ESMF_KIND_R8), dimension(:), intent(out) :: maxdiffR8
    integer,                             intent(out) :: rc

    ! -- local variables
    integer :: fieldCount, item, localDe, localDeCount
    integer(ESMF_KIND_I4) :: maxdI4
    real   (ESMF_KIND_R4) :: maxdR4
    real   (ESMF_KIND_R8) :: maxdR8

    integer(ESMF_KIND_I4), dimension(:,:), pointer :: fpInpI4, fpOutI4
    real   (ESMF_KIND_R4), dimension(:,:), pointer :: fpInpR4, fpOutR4
    real   (ESMF_KIND_R8), dimension(:,:), pointer :: fpInpR8, fpOutR8

    type(ESMF_TypeKind_Flag) :: typekind

    ! -- begin
    rc = ESMF_SUCCESS

    maxdiffI4 = 0_ESMF_KIND_I4
    maxdiffR4 = 0._ESMF_KIND_R4
    maxdiffR8 = 0._ESMF_KIND_R8

    fieldCount = size(inputFields)
    if (fieldCount /= size(outputFields)) then
      call ESMF_LogSetError(ESMF_RC_ARG_SIZE, &
      msg="Size of input and output Fields arrays must match.", &
      line=__LINE__, file=__FILE__, rcToReturn=rc)
      return
    end if

    if ((fieldCount /= size(maxdiffI4)) .or. &
        (fieldCount /= size(maxdiffR4)) .or. &
        (fieldCount /= size(maxdiffR8))) then
      call ESMF_LogSetError(ESMF_RC_ARG_SIZE, &
        msg="Size of maxdiff arguments must match size of input/output Field arrays", &
        line=__LINE__, file=__FILE__, rcToReturn=rc)
      return
    end if

    do item = 1, size(inputFields)
      call ESMF_FieldGet(inputFields(item), localDeCount=localDeCount, &
        typekind=typekind, rc=rc)
      if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
        line=__LINE__, file=__FILE__)) return

      if      (typekind == ESMF_TYPEKIND_I4) then
        print *,'Comparing ESMF_TYPEKIND_I4 Fields'
        do localDe = 0, localDeCount-1
          call ESMF_FieldGet(inputFields(item), localDE=localDe, &
            farrayPtr=fpInpI4, rc=rc)
          if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
            line=__LINE__, file=__FILE__)) return
          call ESMF_FieldGet(outputFields(item), localDE=localDe, &
            farrayPtr=fpOutI4, rc=rc)
          if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
            line=__LINE__, file=__FILE__)) return

          print *,'|write     |, min/max: ', minval(fpOutI4), maxval(fpOutI4)
          print *,'|read      |, min/max: ', minval(fpInpI4), maxval(fpInpI4)
          maxdI4 = maxval(abs(fpOutI4-fpInpI4))
          print *,'|read-write|, min/max: ', minval(abs(fpOutI4-fpInpI4)), maxdI4
          maxdiffI4(item) = max(maxdiffI4(item), maxdI4)
        end do
      else if (typekind == ESMF_TYPEKIND_R4) then
        print *,'Comparing ESMF_TYPEKIND_R4 Fields'
        do localDe = 0, localDeCount-1
          call ESMF_FieldGet(inputFields(item), localDE=localDe, &
            farrayPtr=fpInpR4, rc=rc)
          if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
            line=__LINE__, file=__FILE__)) return
          call ESMF_FieldGet(outputFields(item), localDE=localDe, &
            farrayPtr=fpOutR4, rc=rc)
          if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
            line=__LINE__, file=__FILE__)) return

          print *,'|write     |, min/max: ', minval(fpOutR4), maxval(fpOutR4)
          print *,'|read      |, min/max: ', minval(fpInpR4), maxval(fpInpR4)
          maxdR4 = maxval(abs(fpOutR4-fpInpR4))
          print *,'|read-write|, min/max: ', minval(abs(fpOutR4-fpInpR4)), maxdR4
          maxdiffR4(item) = max(maxdiffR4(item), maxdR4)
        end do
      else if (typekind == ESMF_TYPEKIND_R8) then
        print *,'Comparing ESMF_TYPEKIND_R8 Fields'
        do localDe = 0, localDeCount-1
          call ESMF_FieldGet(inputFields(item), localDE=localDe, &
            farrayPtr=fpInpR8, rc=rc)
          if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
            line=__LINE__, file=__FILE__)) return
          call ESMF_FieldGet(outputFields(item), localDE=localDe, &
            farrayPtr=fpOutR8, rc=rc)
          if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
            line=__LINE__, file=__FILE__)) return

          print *,'|write     |, min/max: ', minval(fpOutR8), maxval(fpOutR8)
          print *,'|read      |, min/max: ', minval(fpInpR8), maxval(fpInpR8)
          maxdR8 = maxval(abs(fpOutR8-fpInpR8))
          print *,'|read-write|, min/max: ', minval(abs(fpOutR8-fpInpR8)), maxdR8
          maxdiffR8(item) = max(maxdiffR8(item), maxdR8)
        end do
      end if
      flush(6)
    end do

  end subroutine IOCompUTestCompare