/[MITgcm]/MITgcm/pkg/mnc/mnc_dim.F
ViewVC logotype

Diff of /MITgcm/pkg/mnc/mnc_dim.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.5 by edhill, Wed Feb 4 05:45:09 2004 UTC revision 1.6 by edhill, Thu Feb 5 00:13:47 2004 UTC
# Line 113  C     Add to tables Line 113  C     Add to tables
113        RETURN        RETURN
114        END        END
115    
116    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
117    
118          SUBROUTINE MNC_DIM_UNLIM_SIZE(
119         I     myThid,
120         I     fname,
121         I     unlim_sz )
122    
123          implicit none
124    #include "netcdf.inc"
125    #include "mnc_common.h"
126    #include "EEPARAMS.h"
127    
128    C     Arguments
129          integer myThid, unlim_sz
130          character*(*) fname
131    
132    C     Functions
133          integer ILNBLNK, IFNBLNK
134    
135    C     Local Variables
136          integer i,j, nf, indf, fid, unlimid, err
137          character*(MAX_LEN_MBUF) msgbuf
138    
139          nf = ILNBLNK(fname)
140    
141    C     Verify that the file exists
142          CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, indf)
143          IF (indf .LT. 1) THEN
144            write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),
145         &       ''' does not exist'
146            CALL print_error(msgbuf, mythid)
147            stop 'ABNORMAL END: S/R MNC_DIM_UNLIM_SIZE'
148          ENDIF
149          fid = mnc_f_info(indf,2)
150    
151    C     Find the unlimited dim and its current size
152          unlim_sz = -1
153          DO i = 1,mnc_f_alld(indf,1)
154            j = mnc_f_alld(indf,i+1)
155            IF (mnc_d_size(j) .EQ. -1) THEN
156              unlimid = mnc_d_ids(j)
157              err = NF_INQ_DIMLEN(fid, unlimid, unlim_sz)
158              write(msgbuf,'(3a)') 'MNC_DIM_UNLIM_SIZE ERROR: cannot ',
159         &         'determine unlimited dim size in file ''', fname(1:nf)
160              CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
161              RETURN
162            ENDIF
163          ENDDO
164    
165          RETURN
166          END
167    
168    
169    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
170    

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.6

  ViewVC Help
Powered by ViewVC 1.1.22