CFIO_DimInquire Subroutine

public subroutine CFIO_DimInquire(fid, im, jm, km, lm, nvars, ngatts, vdir, rc)

CFIO_DimInquire – Gets dimension information from a CFIO file.

This routine is used to get dimension information from an existing CFIO file. This dimension information can subsequently be used to allocate arrays for reading data from the file. For more complete information about the contents of a file, Cfio_Inquire should be used.

History

  • 1998.07.02 Lucchesi Initial interface design.
  • 1998.08.05 Lucchesi Added “ngatts”
  • 1998.09.24 Lucchesi Revamped error codes
  • 1998.12.22 Lucchesi Added IdentifyDim and associated code
  • 1999.01.04 Lucchesi Changed variable initialization
  • 2008.03.14 Kokron Initialize stationFile to false

Arguments

Type IntentOptional Attributes Name
integer :: fid
integer :: im

Size of longitudinal dimension

integer :: jm

Size of latitudinal dimension

integer :: km

Size of vertical dimension km=0 if surface-only file

integer :: lm

Number of times

integer :: nvars

Number of variables

integer :: ngatts

Number of global attributes

integer, optional :: vdir

Positive vertical direction. If -1, level 1 in the file is TOA. If 1, level 1 in the file is the surface. If 0, the file has no vertical co-ordinate (default).

integer, optional :: rc

Error return code: rc = 0 all is well rc = -19 unable to identify coordinate variable

NetCDF Errors


rc = -40 error from NF90_INQ_VARID rc = -41 error from NF90_INQ_DIMID or NF90_INQUIRE_DIMENSION (lat or lon) rc = -42 error from NF90_INQ_DIMID or NF90_INQUIRE_DIMENSION (lev) rc = -43 error from NF90_INQ_VARID (time variable) rc = -47 error from NF90_INQ_DIMID or NF90_INQUIRE_DIMENSION (time) rc = -48 error from NF90_INQUIRE rc = -53 error from NF90_GET_ATT


Calls

proc~~cfio_diminquire~~CallsGraph proc~cfio_diminquire CFIO_DimInquire nf90_get_att nf90_get_att proc~cfio_diminquire->nf90_get_att nf90_inq_varid nf90_inq_varid proc~cfio_diminquire->nf90_inq_varid nf90_inquire nf90_inquire proc~cfio_diminquire->nf90_inquire nf90_inquire_dimension nf90_inquire_dimension proc~cfio_diminquire->nf90_inquire_dimension nf90_inquire_variable nf90_inquire_variable proc~cfio_diminquire->nf90_inquire_variable proc~err err proc~cfio_diminquire->proc~err proc~identifydim IdentifyDim proc~cfio_diminquire->proc~identifydim

Called by

proc~~cfio_diminquire~~CalledByGraph proc~cfio_diminquire CFIO_DimInquire proc~esmf_cfiosdffileopen ESMF_CFIOSdfFileOpen proc~esmf_cfiosdffileopen->proc~cfio_diminquire proc~esmf_cfiofileopen ESMF_CFIOFileOpen proc~esmf_cfiofileopen->proc~esmf_cfiosdffileopen none~find~4 CFIOCollection%find none~find~4->proc~esmf_cfiofileopen proc~mapl_cfioopenwrite MAPL_CFIOOpenWrite proc~mapl_cfioopenwrite->proc~esmf_cfiofileopen program~test~11 test program~test~11->proc~esmf_cfiofileopen program~test~2 test program~test~2->proc~esmf_cfiofileopen program~test~4 test program~test~4->proc~esmf_cfiofileopen program~test~6 test program~test~6->proc~esmf_cfiofileopen proc~mapl_cfiocreatefromfile MAPL_CFIOCreateFromFile proc~mapl_cfiocreatefromfile->none~find~4 proc~mapl_cfioreadbundleread MAPL_CFIOReadBundleRead proc~mapl_cfioreadbundleread->none~find~4

Source Code

      subroutine CFIO_DimInquire (fid,im,jm,km,lm,nvars,ngatts,vdir,rc)
!
! !USES:
!
      Implicit NONE
!
! !INPUT PARAMETERS:
!
      integer        fid              ! File handle
!
! !OUTPUT PARAMETERS:
!
      integer     im     !! Size of longitudinal dimension
      integer     jm     !! Size of latitudinal dimension
      integer     km     !! Size of vertical dimension
                         !!   km=0 if surface-only file
      integer     lm     !! Number of times
      integer     nvars  !! Number of variables
      integer     ngatts !! Number of global attributes
      integer, optional :: vdir   !! Positive vertical direction.
                         !! If `-1`, level 1 in the file is TOA.
                         !! If `1`, level 1 in the file is the surface.
                         !! If `0`, the file has no vertical co-ordinate (default).
      integer, optional :: rc     !! Error return code:
                         !!  rc = 0    all is well
                         !!  rc = -19  unable to identify coordinate variable
                         !!
                         !!  NetCDF Errors
                         !!  -------------
                         !!  rc = -40  error from NF90_INQ_VARID
                         !!  rc = -41  error from NF90_INQ_DIMID or NF90_INQUIRE_DIMENSION (lat or lon)
                         !!  rc = -42  error from NF90_INQ_DIMID or NF90_INQUIRE_DIMENSION (lev)
                         !!  rc = -43  error from NF90_INQ_VARID (time variable)
                         !!  rc = -47  error from NF90_INQ_DIMID or NF90_INQUIRE_DIMENSION (time)
                         !!  rc = -48  error from NF90_INQUIRE
                         !!  rc = -53  error from NF90_GET_ATT
!
!-------------------------------------------------------------------------

      integer dimId, i
      character(len=MAXCHR) dimName
      character(len=MAXCHR) stdName
      character(len=MAXCHR) dimUnits
      character(len=MAXCHR) posStr
      character(len=MAXCHR) vname
      integer dimSize
      integer nDims
      logical surfaceOnly
      logical stationFile
      integer myIndex
      integer varType, nvDims, vDims(MAXVDIMS), nvAtts
      integer tmpNvar
      logical :: cs_found
      integer :: vdir_
      integer :: found_xc, found_yc,vid

! Initialize variables

      surfaceOnly = .FALSE.
      stationFile = .false.
      vdir_       = -1 ! Assume 3D and same orientation
      found_xc = 0
      found_yc = 0

! Check FID here.

! Check to make sure max string lengths are large enough.  NetCDF defines
! MAXNCNAM, but it can't be used in a character(len=MAXNCNAM) statement.

      if (MAXCHR .LT. MAXNCNAM) then
        print *, 'CFIO_DimInquire warning: MAXNCNAM is larger than ', &
                'dimName array size.'
      endif

! Get basic information from file.


      rc = NF90_INQUIRE(fid, nDims, nvars, ngatts, dimId)
      if (err("DimInqure: NF90_INQUIRE failed",rc,-48) .NE. 0)return

! Subtract dimension variables from the variable count.

      cs_found = .false.
      tmpNvar = nvars
      do i=1,nvars
        rc = NF90_INQUIRE_VARIABLE (fid,i,vname,varType,nvDims,vDims,nvAtts)
        if (err("DimInquire: variable inquire error",rc,-52) .NE. 0) &
           return
        if (nvDims .EQ. 1 .or. trim(vname) .eq. 'time_bnds') then
          tmpNvar = tmpNvar - 1
        endif
        if (vname == 'nf') then
           cs_found = .true.
        end if
      enddo
      if (cs_found) then
         tmpNvar = tmpNvar - 4
         found_xc = NF90_INQ_VARID(fid,"corner_lons",vid)
         if (found_xc ==0) tmpNvar = tmpNvar - 1
         found_yc = NF90_INQ_VARID(fid,"corner_lats",vid)
         if (found_yc ==0) tmpNvar = tmpNvar - 1
      end if
      nvars = tmpNvar

! Extract dimension information

      do i=1,nDims
        rc = NF90_INQUIRE_DIMENSION (fid, i, dimName, dimSize)
        if (err("DimInqure: can't get dim info",rc,-41) .NE. 0) return
        if (index(dimName,'station') .gt. 0) then
           stationFile = .true.
           im = dimSize
           jm = dimSize
           cycle
        end if
        if (trim(dimName) .eq. 'nv') cycle
        if (trim(dimName) .eq. 'nf') cycle
        if (trim(dimName) .eq. 'ncontact') cycle
        if (trim(dimName) .eq. 'XCdim') cycle
        if (trim(dimName) .eq. 'YCdim') cycle
        if (trim(dimName) .eq. 'orientationStrLen') cycle

        rc = NF90_INQ_VARID (fid, dimName, dimId)
        if (err("DimInqure: NF90_INQ_VARID failed",rc,-40) .NE. 0) return
        ! If it has the standard_name attribute, use that instead
        rc = NF90_GET_ATT(fid,dimId,'standard_name',stdName)
        if (rc .ne. 0) stdName = Trim(dimName)
        dimunits = ''
        rc = NF90_GET_ATT(fid,dimId,'units',dimUnits)
        if (.not. cs_found) then !ALT: the new cubed-sphere format might be missing some units
           if (err("DimInqure: could not get units for dimension",rc,-53)&
                .NE. 0) return
        end if
        myIndex = IdentifyDim (dimName, dimUnits)
        if ( myIndex .EQ. 0 ) then
          im = dimSize
        else if ( myIndex .EQ. 1 ) then
          jm = dimSize
          if(cs_found) jm = jm*6
        else if ( myIndex .EQ. 2 ) then
          km = dimSize
          if (km.eq.1) then
             ! 2D
             vdir_ = 0
          else
             rc = NF90_GET_ATT(fid,dimId,'positive',posStr)
             if (rc.eq.0) then
                if ((Trim(posStr)=="up").or.(Trim(posStr)=="Up")) then
                   ! Level 1 = surface
                   vdir_ = 1
                elseif ((Trim(posStr)=="down").or.(Trim(posStr)=="Down")) then
                   ! Level 1 = TOA
                   vdir_ = -1
                endif
             endif
          endif

        else if ( myIndex .EQ. 3 ) then
          lm = dimSize
!print *, "dimUnits: ", trim(dimUnits)
!print *, "dimName: ", trim(dimName)
!        else
!          print *, 'CFIO_DimInquire: Coordinate variable ',       &
!                  TRIM(dimName),' with units of ',TRIM(dimUnits), &
!                  ' is not understood.'
!          rc = -19
!          return
        endif
      enddo

      if (cs_found .and. nDims == 6) surfaceOnly = .TRUE.
      if (cs_found .and. nDims == 8) surfaceOnly = .TRUE.
      if (nDims .EQ. 3 .and. .NOT. stationFile) then
        surfaceOnly = .TRUE.
      endif

      if (surfaceOnly) then
        km = 0
        vdir_ = 0
      endif

      if (present(vdir)) vdir = vdir_
      rc=0
      return
      end subroutine CFIO_DimInquire