ESMF_MeshCreateFromScrip Function

private function ESMF_MeshCreateFromScrip(filename, convertToDual, addUSerArea, rc)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
logical, intent(in), optional :: convertToDual
logical, intent(in), optional :: addUSerArea
integer, intent(out), optional :: rc

Return Value type(ESMF_Mesh)


Source Code

    function ESMF_MeshCreateFromScrip(filename, convertToDual, addUserArea, rc)
!
!
! !RETURN VALUE:
    type(ESMF_Mesh)         :: ESMF_MeshCreateFromScrip
! !ARGUMENTS:
    character(len=*), intent(in)                   :: filename
    logical, intent(in), optional                  :: convertToDual
    logical, intent(in), optional                  :: addUSerArea
    integer, intent(out), optional                 :: rc
!
! !DESCRIPTION:
!   Create a mesh from a grid file defined in SCRIP format or in ESMF Unstructured grid format.
!
!   \begin{description}
!   \item [filename]
!         The name of the grid file
!   \item[convertToDual]
!         if {\tt .true.}, the mesh will be converted to it's dual. If not specified,
!         defaults to .false.
!   \item[addUserArea]
!         if {\tt .true.}, the grid_area defined in the grid file will be added into the mesh.
!         If not specified, defaults to .false.
!   \item [{[rc]}]
!         Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!   \end{description}
!
!EOPI
!------------------------------------------------------------------------------
    integer                 :: localrc           ! local return code
    character(len=128)      :: cmd, esmffilename
    integer                 :: PetNo, PetCnt
    integer                 :: scrip_file_len, esmf_file_len
    type(ESMF_VM)           :: vm
    integer                 :: dualflag
    integer                 :: unit
    logical                 :: notavail
    integer                 :: gridRank
    integer,pointer         :: gridDims(:)
    integer                 :: poleVal, minPoleGid, maxPoleGid,poleObjType

    ! Initialize return code; assume failure until success is certain
    localrc = ESMF_RC_NOT_IMPL
    if (present(rc)) rc = ESMF_RC_NOT_IMPL

    ! Default convert to dual
    if (present(convertToDual)) then
       if (convertToDual) then
          dualflag=1
       else
          dualflag=0
       endif
    else
      dualflag=0
    endif

    ! If convertToDual is TRUE, cannot use UserArea because the area defined
    ! in the grid file is not for the dual mesh
    if (present(addUserArea)) then
      if (addUserArea .and. dualflag==1) then
         call ESMF_LogSetError(ESMF_RC_ARG_BAD, &
              msg="- Cannot use user area when convertToDual flag is set to TRUE", &
              ESMF_CONTEXT, rcToReturn=rc)
         return
      endif
    endif

    ! get global vm information
    !
    call ESMF_VMGetCurrent(vm, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return

    ! set up local pet info
    call ESMF_VMGet(vm, localPet=PetNo, petCount=PetCnt, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return

    esmffilename = ".esmf.nc"

    if (PetNo == 0) then
        ! this is a serial call into C code for now
        call c_ConvertSCRIP(filename, esmffilename,  &
          dualflag, localrc )
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    call ESMF_VMBarrier(vm)
    ESMF_MeshCreateFromScrip=ESMF_MeshCreateFromUnstruct(esmffilename,&
        addUserArea=addUserArea, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return
    if (PetNo == 0) then
!      system() is not available on some of the compilers, use open/close to
!      delete the file instead
!      write(cmd, '("/bin/rm ",A)') trim(esmffilename)
!      call system(cmd)
!      First find an available unit numer

       call ESMF_UtilIOUnitGet(unit, rc=rc)
       if (rc==ESMF_SUCCESS) then
          open(unit, FILE=esmffilename,status='unknown')
          close(unit, STATUS='delete')
       endif
    endif

   ! Add pole information, if created from a 2D grid file
    allocate(gridDims(2))
    call ESMF_ScripInq(filename, grid_rank=gridRank, grid_dims=gridDims, rc=localrc)
    if (ESMF_LogFoundError(localrc, &
         ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return

    if (gridRank==2) then
       ! Choose which object type to set based on whether this is a dual or not
       poleObjType=1 ! Set elems
       if (dualflag==1) poleObjType=0 ! Elems have been converted to nodes, so set nodes

      ! Set pole val to 4
       poleVal=4
       minPoleGid=1
       maxPoleGid=gridDims(1)
       call C_ESMC_MeshSetPoles(ESMF_MeshCreateFromScrip, poleObjType, &
            poleVal, minPoleGid, maxPoleGid, localrc)
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return

      ! Set pole val to 5
       poleVal=5
       minPoleGid=gridDims(1)*gridDims(2)-gridDims(1)+1
       maxPoleGid=gridDims(1)*gridDims(2)
       call C_ESMC_MeshSetPoles(ESMF_MeshCreateFromScrip, poleObjType, &
            poleVal, minPoleGid, maxPoleGid, localrc)
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return
    endif

    if (associated(gridDims)) deallocate(gridDims)

    ! Output success
    if (present(rc)) rc=ESMF_SUCCESS
    return
end function ESMF_MeshCreateFromScrip