/[MITgcm]/MITgcm/pkg/mnc/mnc_cw_readwrite.template
ViewVC logotype

Annotation of /MITgcm/pkg/mnc/mnc_cw_readwrite.template

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


Revision 1.9 - (hide annotations) (download)
Fri Mar 19 03:28:36 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
Changes since 1.8: +43 -41 lines
 o edit all MNC subroutines so that myThid is the _last_ argument

1 edhill 1.9 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.8 2004/03/10 05:50:16 edhill Exp $
2 edhill 1.1 C $Name: $
3    
4     #include "MNC_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8 edhill 1.3 SUBROUTINE MNC_CW_RX_W_YY(
9 edhill 1.1 I fbname, bi,bj,
10     I vtype,
11     I indu,
12 edhill 1.9 I var,
13     I myThid )
14 edhill 1.1
15     implicit none
16    
17     #include "netcdf.inc"
18     #include "mnc_common.h"
19     #include "EEPARAMS.h"
20 edhill 1.2 #include "SIZE.h"
21    
22     #define mnc_rtype_YY
23 edhill 1.1
24     C Arguments
25     integer myThid, bi,bj, indu
26     character*(*) fbname, vtype
27 edhill 1.6 __V var(*)
28 edhill 1.1
29     C Functions
30     integer IFNBLNK, ILNBLNK
31    
32     C Local Variables
33 edhill 1.3 integer i,j,k, indv,nvf,nvl, n1,n2, igrid, ntot
34 edhill 1.2 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv, indvids
35 edhill 1.3 integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
36     integer p(9),s(9),e(9), dimnc(9), vstart(9),vcount(9), udo(9)
37     integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
38 edhill 1.1 character*(MAX_LEN_MBUF) msgbuf
39     character*(MNC_MAX_CHAR) fname
40    
41     C Temporary storage for the simultaneous type conversion and
42     C re-shaping before passing to NetCDF
43     #ifdef mnc_rtype_D
44 edhill 1.6 REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
45 edhill 1.1 #endif
46     #ifdef mnc_rtype_R
47 edhill 1.6 REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
48     #endif
49     #ifdef mnc_rtype_I
50     INTEGER resh( sNx + 2*OLx + sNy + 2*OLy )
51 edhill 1.1 #endif
52    
53     C Only do I/O if I am the master thread
54     _BEGIN_MASTER( myThid )
55    
56     C Check that the Variable Type exists
57     nvf = IFNBLNK(vtype)
58     nvl = ILNBLNK(vtype)
59 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, vtype, mnc_cw_vname, indv, myThid)
60 edhill 1.2 IF (indv .LT. 1) THEN
61 edhill 1.6 write(msgbuf,'(3a)') 'MNC_CW_RX_W_YY ERROR: vtype ''',
62 edhill 1.2 & vtype(nvf:nvl), ''' is not defined'
63 edhill 1.1 CALL print_error(msgbuf, mythid)
64 edhill 1.6 STOP 'ABNORMAL END: S/R MNC_CW_RX_W_YY'
65 edhill 1.1 ENDIF
66 edhill 1.2 igrid = mnc_cw_vgind(indv)
67 edhill 1.1
68 edhill 1.5 C Set the bi,bj indicies
69 edhill 1.2 bis = bi
70     bie = bi
71 edhill 1.1 IF (bi .LT. 1) THEN
72     bis = 1
73     bie = nSx
74     ENDIF
75 edhill 1.2 bjs = bj
76     bje = bj
77 edhill 1.1 IF (bj .LT. 1) THEN
78     bjs = 1
79     bje = nSy
80     ENDIF
81    
82 edhill 1.2 DO lbj = bjs,bje
83     DO lbi = bis,bie
84 edhill 1.1
85     C Create the file name
86 edhill 1.9 CALL MNC_CW_GET_TILE_NUM(lbi,lbj, uniq_tnum, myThid)
87 edhill 1.1 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
88     n1 = IFNBLNK(fbname)
89     n2 = ILNBLNK(fbname)
90     ntot = n2 - n1 + 1
91     fname(1:ntot) = fbname(n1:n2)
92     ntot = ntot + 1
93     fname(ntot:ntot) = '.'
94     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
95 edhill 1.2 nfname = ntot+9
96    
97     C Append to an existing or create a new file
98 edhill 1.9 CALL MNC_CW_FILE_AORC(fname, indf, myThid)
99 edhill 1.2 fid = mnc_f_info(indf,2)
100    
101 edhill 1.3 C Ensure that all the NetCDF dimensions are defined and create a
102     C local copy of them
103 edhill 1.2 DO i = 1,9
104     dimnc(i) = 1
105     ENDDO
106     DO i = 1,mnc_cw_ndim(igrid)
107 edhill 1.3 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
108     dimnc(i) = -1
109     ELSE
110     dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
111     ENDIF
112 edhill 1.9 CALL MNC_DIM_INIT(fname,
113     & mnc_cw_dn(i,igrid), dimnc(i), myThid)
114 edhill 1.2 ENDDO
115    
116     C Ensure that the "grid" is defined
117 edhill 1.9 CALL MNC_GRID_INIT(fname, mnc_cw_gname(igrid),
118     & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)
119 edhill 1.2
120     C Ensure that the variable is defined
121     #ifdef mnc_rtype_D
122 edhill 1.9 CALL MNC_VAR_INIT_DBL(fname,mnc_cw_gname(igrid),vtype, myThid)
123 edhill 1.2 #endif
124     #ifdef mnc_rtype_R
125 edhill 1.9 CALL MNC_VAR_INIT_REAL(fname,mnc_cw_gname(igrid),vtype, myThid)
126 edhill 1.2 #endif
127 edhill 1.6 #ifdef mnc_rtype_I
128 edhill 1.9 CALL MNC_VAR_INIT_INT(fname,mnc_cw_gname(igrid),vtype, myThid)
129 edhill 1.6 #endif
130 edhill 1.2 DO i = 1,mnc_fv_ids(indf,1)
131     j = 2 + 3*(i - 1)
132     IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
133     idv = mnc_fv_ids(indf,j+1)
134     indvids = mnc_fd_ind(indf, mnc_f_info(indf,
135     & (mnc_fv_ids(indf,j+2) + 1)) )
136     GOTO 10
137     ENDIF
138     ENDDO
139 edhill 1.6 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_W_YY ERROR: ',
140 edhill 1.2 & 'cannot reference variable ''', vtype, ''''
141     CALL print_error(msgbuf, mythid)
142 edhill 1.5 STOP 'ABNORMAL END: package MNC'
143 edhill 1.2 10 CONTINUE
144    
145 edhill 1.3 C Check for bi,bj indicies
146     bidim = mnc_cw_vbij(1,indv)
147     bjdim = mnc_cw_vbij(2,indv)
148 edhill 1.4 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
149 edhill 1.3
150 edhill 1.2 C Set the dimensions for the in-memory array
151     ndim = mnc_cw_ndim(igrid)
152 edhill 1.3 k = mnc_cw_dims(1,igrid)
153     IF (k .GT. 0) THEN
154     p(1) = k
155     ELSE
156     p(1) = 1
157     ENDIF
158 edhill 1.2 DO i = 2,9
159 edhill 1.3 k = mnc_cw_dims(i,igrid)
160     IF (k .LT. 1) THEN
161     k = 1
162     ENDIF
163     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
164     p(i) = nSx * p(i-1)
165     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
166     p(i) = nSy * p(i-1)
167     ELSE
168     p(i) = k * p(i-1)
169     ENDIF
170 edhill 1.2 ENDDO
171    
172 edhill 1.3 C Set starting and ending indicies for the in-memory array and
173     C the unlimited dimension offset for the NetCDF array
174 edhill 1.2 DO i = 1,9
175 edhill 1.3 udo(i) = 0
176     s(i) = 1
177     e(i) = 1
178     IF (i .LE. ndim) THEN
179     s(i) = mnc_cw_is(i,igrid)
180     e(i) = mnc_cw_ie(i,igrid)
181     ENDIF
182     C Check for the unlimited dimension
183     IF ((i .EQ. ndim)
184     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
185     IF (indu .GT. 0) THEN
186     C Use the indu value
187     udo(i) = indu - 1
188     ELSEIF (indu .EQ. -1) THEN
189     C Append one to the current unlimited dim size
190 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
191 edhill 1.3 udo(i) = unlim_sz
192 edhill 1.2 ELSE
193 edhill 1.3 C Use the current unlimited dim size
194 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
195 edhill 1.3 udo(i) = unlim_sz - 1
196 edhill 1.2 ENDIF
197     ENDIF
198     ENDDO
199 edhill 1.3 IF (bidim .GT. 0) THEN
200     s(bidim) = lbi
201     e(bidim) = lbi
202     ENDIF
203     IF (bjdim .GT. 0) THEN
204     s(bjdim) = lbj
205     e(bjdim) = lbj
206     ENDIF
207 edhill 1.4 CEH3 DO i = 1,9
208     CEH3 write(*,*) 'i,p(i),s(i),e(i) = ', i,p(i),s(i),e(i)
209     CEH3 ENDDO
210 edhill 1.3
211     C Add the global attributes
212 edhill 1.9 CALL MNC_CW_SET_GATTR( fname, lbi,lbj, uniq_tnum, myThid)
213 edhill 1.3
214     C Add the per-variable attributes
215     DO i = 1,mnc_cw_vnat(1,indv)
216 edhill 1.9 CALL MNC_VAR_ADD_ATTR_STR( fname, vtype,
217     & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv), myThid)
218 edhill 1.3 ENDDO
219     DO i = 1,mnc_cw_vnat(2,indv)
220 edhill 1.9 CALL MNC_VAR_ADD_ATTR_INT( fname, vtype,
221     & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv), myThid)
222 edhill 1.3 ENDDO
223     DO i = 1,mnc_cw_vnat(3,indv)
224 edhill 1.9 CALL MNC_VAR_ADD_ATTR_DBL( fname, vtype,
225     & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv), myThid)
226 edhill 1.3 ENDDO
227 edhill 1.2
228 edhill 1.9 CALL MNC_FILE_ENDDEF(fname, myThid)
229 edhill 1.2
230 edhill 1.8 write(msgbuf,'(5a)') 'writing variable type ''',
231     & vtype(nvf:nvl), ''' within file ''',
232     & fname(1:nfname), ''''
233    
234 edhill 1.2 C Write the variable one vector at a time
235 edhill 1.3 DO j7 = s(7),e(7)
236 edhill 1.4 k7 = (j7 - 1)*p(6)
237 edhill 1.3 vstart(7) = udo(7) + j7 - s(7) + 1
238     vcount(7) = 1
239     DO j6 = s(6),e(6)
240 edhill 1.4 k6 = (j6 - 1)*p(5) + k7
241 edhill 1.3 vstart(6) = udo(6) + j6 - s(6) + 1
242     vcount(6) = 1
243     DO j5 = s(5),e(5)
244 edhill 1.4 k5 = (j5 - 1)*p(4) + k6
245 edhill 1.3 vstart(5) = udo(5) + j5 - s(5) + 1
246     vcount(5) = 1
247     DO j4 = s(4),e(4)
248 edhill 1.4 k4 = (j4 - 1)*p(3) + k5
249 edhill 1.3 vstart(4) = udo(4) + j4 - s(4) + 1
250     vcount(4) = 1
251     DO j3 = s(3),e(3)
252 edhill 1.4 k3 = (j3 - 1)*p(2) + k4
253 edhill 1.3 vstart(3) = udo(3) + j3 - s(3) + 1
254     vcount(3) = 1
255     DO j2 = s(2),e(2)
256 edhill 1.4 k2 = (j2 - 1)*p(1) + k3
257 edhill 1.3 vstart(2) = udo(2) + j2 - s(2) + 1
258     vcount(2) = 1
259 edhill 1.1
260 edhill 1.3 kr = 0
261     DO j1 = s(1),e(1)
262     k1 = k2 + j1
263     kr = kr + 1
264     resh(kr) = var(k1)
265     ENDDO
266    
267     vstart(1) = udo(1) + 1
268     vcount(1) = e(1) - s(1) + 1
269 edhill 1.2
270     #ifdef mnc_rtype_D
271     err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
272     #endif
273     #ifdef mnc_rtype_R
274     err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh)
275     #endif
276 edhill 1.6 #ifdef mnc_rtype_I
277     err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh)
278     #endif
279 edhill 1.1
280 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
281 edhill 1.8
282 edhill 1.3 ENDDO
283     ENDDO
284 edhill 1.2 ENDDO
285     ENDDO
286     ENDDO
287     ENDDO
288    
289     C Sync the file
290     err = NF_SYNC(fid)
291     write(msgbuf,'(3a)') 'sync for file ''', fname,
292 edhill 1.6 & ''' in S/R MNC_CW_RX_W_YY'
293 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
294 edhill 1.5
295     ENDDO
296     ENDDO
297    
298     _END_MASTER( myThid )
299    
300     RETURN
301     END
302    
303    
304     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
305    
306    
307     SUBROUTINE MNC_CW_RX_R_YY(
308     I fbname, bi,bj,
309     I vtype,
310     I indu,
311 edhill 1.9 I var,
312     I myThid )
313 edhill 1.5
314     implicit none
315    
316     #include "netcdf.inc"
317     #include "mnc_common.h"
318     #include "EEPARAMS.h"
319     #include "SIZE.h"
320    
321     #define mnc_rtype_YY
322    
323     C Arguments
324     integer myThid, bi,bj, indu
325     character*(*) fbname, vtype
326 edhill 1.6 __V var(*)
327 edhill 1.5
328     C Functions
329     integer IFNBLNK, ILNBLNK
330    
331     C Local Variables
332 edhill 1.8 integer i,k, nvf,nvl, n1,n2, igrid, ntot
333 edhill 1.6 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv
334 edhill 1.5 integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
335 edhill 1.6 integer ind_fv_ids, ind_vt, ierr, atype, alen
336     integer f_sNx,f_sNy, ires
337     integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)
338     integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
339 edhill 1.5 character*(MAX_LEN_MBUF) msgbuf
340     character*(MNC_MAX_CHAR) fname
341    
342     C Temporary storage for the simultaneous type conversion and
343     C re-shaping before passing to NetCDF
344     #ifdef mnc_rtype_D
345 edhill 1.6 REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
346 edhill 1.5 #endif
347     #ifdef mnc_rtype_R
348 edhill 1.6 REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
349     #endif
350     #ifdef mnc_rtype_I
351     INTEGER resh( sNx + 2*OLx + sNy + 2*OLy )
352 edhill 1.5 #endif
353    
354     C Only do I/O if I am the master thread
355     _BEGIN_MASTER( myThid )
356    
357     C Check that the Variable Type exists
358     nvf = IFNBLNK(vtype)
359     nvl = ILNBLNK(vtype)
360 edhill 1.9 CALL MNC_GET_IND( MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt, myThid)
361 edhill 1.7 IF (ind_vt .LT. 1) THEN
362 edhill 1.5 write(msgbuf,'(3a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
363     & vtype(nvf:nvl), ''' is not defined'
364     CALL print_error(msgbuf, mythid)
365     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
366     ENDIF
367     igrid = mnc_cw_vgind(ind_vt)
368    
369     C Check for bi,bj indicies
370 edhill 1.6 bidim = mnc_cw_vbij(1,ind_vt)
371     bjdim = mnc_cw_vbij(2,ind_vt)
372 edhill 1.5
373     C Set the bi,bj indicies
374     bis = bi
375     bie = bi
376     IF (bi .LT. 1) THEN
377     bis = 1
378     bie = nSx
379     ENDIF
380     bjs = bj
381     bje = bj
382     IF (bj .LT. 1) THEN
383     bjs = 1
384     bje = nSy
385     ENDIF
386    
387     DO lbj = bjs,bje
388     DO lbi = bis,bie
389    
390     C Create the file name
391 edhill 1.9 CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)
392 edhill 1.5 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
393     n1 = IFNBLNK(fbname)
394     n2 = ILNBLNK(fbname)
395     ntot = n2 - n1 + 1
396     fname(1:ntot) = fbname(n1:n2)
397     ntot = ntot + 1
398     fname(ntot:ntot) = '.'
399     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
400     nfname = ntot+9
401    
402     C Open the existing file
403 edhill 1.9 CALL MNC_FILE_TRY_READ( fname, ierr, indf, myThid)
404 edhill 1.5
405     C Check that the variable (VType) is defined within the file
406 edhill 1.9 CALL MNC_GET_FVINDS( fname, vtype, indf, ind_fv_ids, myThid)
407 edhill 1.5 IF ((indf .LT. 1) .OR. (ind_fv_ids .LT. 1)) THEN
408     write(msgbuf,'(4a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
409     & vtype(nvf:nvl), ''' is not defined within file ''',
410     & fname(1:nfname)
411     CALL print_error(msgbuf, mythid)
412     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
413     ENDIF
414     fid = mnc_f_info(indf,2)
415 edhill 1.6 idv = mnc_fv_ids(indf,ind_fv_ids+1)
416    
417     C Check that the current sNy,sNy values and the in-file values
418     C are compatible and WARN (only warn) if not
419     f_sNx = -1
420     f_sNy = -1
421     err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNx',atype,alen)
422     IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
423     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', f_sNx)
424 edhill 1.9 CALL MNC_HANDLE_ERR(err,
425     & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R_YY',
426     & myThid)
427 edhill 1.6 ENDIF
428     err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNy',atype,alen)
429     IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
430     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', f_sNy)
431 edhill 1.9 CALL MNC_HANDLE_ERR(err,
432     & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R_YY',
433     & myThid)
434 edhill 1.6 ENDIF
435 edhill 1.5 IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
436 edhill 1.6 write(msgbuf,'(5a)') 'MNC_CW_RX_R_YY WARNING: the ',
437     & 'attributes ''sNx'' and ''sNy'' within the file ''',
438     & fname(1:nfname), ''' do not exist or do not match ',
439     & 'the current sizes within the model'
440 edhill 1.5 CALL print_error(msgbuf, mythid)
441     ENDIF
442    
443 edhill 1.6 C Check that the in-memory variable and the in-file variables
444     C are of compatible sizes
445 edhill 1.8 C ires = 1
446 edhill 1.9 C CALL MNC_CHK_VTYP_R_NCVAR( ind_vt,
447 edhill 1.8 C & indf, ind_fv_ids, indu, ires)
448     C IF (ires .LT. 0) THEN
449     C write(msgbuf,'(7a)') 'MNC_CW_RX_R_YY WARNING: the sizes ',
450     C & 'of the in-program variable ''', vtype(nvf:nvl),
451     C & ''' and the corresponding variable within file ''',
452     C & fname(1:nfname), ''' are not compatible -- please ',
453     C & 'check the sizes'
454     C CALL print_error(msgbuf, mythid)
455     C STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
456     C ENDIF
457 edhill 1.5
458 edhill 1.6 C Check for bi,bj indicies
459     bidim = mnc_cw_vbij(1,ind_vt)
460     bjdim = mnc_cw_vbij(2,ind_vt)
461    
462     C Set the dimensions for the in-memory array
463     ndim = mnc_cw_ndim(igrid)
464     k = mnc_cw_dims(1,igrid)
465     IF (k .GT. 0) THEN
466     p(1) = k
467     ELSE
468     p(1) = 1
469     ENDIF
470     DO i = 2,9
471     k = mnc_cw_dims(i,igrid)
472     IF (k .LT. 1) THEN
473     k = 1
474     ENDIF
475     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
476     p(i) = nSx * p(i-1)
477     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
478     p(i) = nSy * p(i-1)
479     ELSE
480     p(i) = k * p(i-1)
481     ENDIF
482     ENDDO
483    
484     C Set starting and ending indicies for the in-memory array and
485     C the unlimited dimension offset for the NetCDF array
486     DO i = 1,9
487     udo(i) = 0
488     s(i) = 1
489     e(i) = 1
490     IF (i .LE. ndim) THEN
491     s(i) = mnc_cw_is(i,igrid)
492     e(i) = mnc_cw_ie(i,igrid)
493     ENDIF
494     C Check for the unlimited dimension
495     IF ((i .EQ. ndim)
496     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
497     IF (indu .GT. 0) THEN
498     C Use the indu value
499     udo(i) = indu - 1
500     ELSEIF (indu .EQ. -1) THEN
501     C Append one to the current unlimited dim size
502 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
503 edhill 1.6 udo(i) = unlim_sz
504     ELSE
505     C Use the current unlimited dim size
506 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
507 edhill 1.6 udo(i) = unlim_sz - 1
508     ENDIF
509     ENDIF
510     ENDDO
511     IF (bidim .GT. 0) THEN
512     s(bidim) = lbi
513     e(bidim) = lbi
514     ENDIF
515     IF (bjdim .GT. 0) THEN
516     s(bjdim) = lbj
517     e(bjdim) = lbj
518     ENDIF
519    
520 edhill 1.8 C DO i = 9,1,-1
521     C write(*,*) 'i,p(i),s(i),e(i) = ', i,': ',p(i),s(i),e(i)
522     C ENDDO
523 edhill 1.6
524 edhill 1.9 CALL MNC_FILE_ENDDEF(fname, myThid)
525 edhill 1.6
526     write(msgbuf,'(5a)') 'reading variable type ''',
527     & vtype(nvf:nvl), ''' within file ''',
528     & fname(1:nfname), ''''
529    
530     C Read the variable one vector at a time
531     DO j7 = s(7),e(7)
532     k7 = (j7 - 1)*p(6)
533     vstart(7) = udo(7) + j7 - s(7) + 1
534     vcount(7) = 1
535     DO j6 = s(6),e(6)
536     k6 = (j6 - 1)*p(5) + k7
537     vstart(6) = udo(6) + j6 - s(6) + 1
538     vcount(6) = 1
539     DO j5 = s(5),e(5)
540     k5 = (j5 - 1)*p(4) + k6
541     vstart(5) = udo(5) + j5 - s(5) + 1
542     vcount(5) = 1
543     DO j4 = s(4),e(4)
544     k4 = (j4 - 1)*p(3) + k5
545     vstart(4) = udo(4) + j4 - s(4) + 1
546     vcount(4) = 1
547     DO j3 = s(3),e(3)
548     k3 = (j3 - 1)*p(2) + k4
549     vstart(3) = udo(3) + j3 - s(3) + 1
550     vcount(3) = 1
551     DO j2 = s(2),e(2)
552     k2 = (j2 - 1)*p(1) + k3
553     vstart(2) = udo(2) + j2 - s(2) + 1
554     vcount(2) = 1
555    
556     vstart(1) = udo(1) + 1
557     vcount(1) = e(1) - s(1) + 1
558    
559     #ifdef mnc_rtype_D
560     err = NF_GET_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
561     #endif
562     #ifdef mnc_rtype_R
563     err = NF_GET_VARA_REAL(fid, idv, vstart, vcount, resh)
564     #endif
565     #ifdef mnc_rtype_I
566     err = NF_GET_VARA_INT(fid, idv, vstart, vcount, resh)
567     #endif
568    
569 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
570 edhill 1.6
571     kr = 0
572     DO j1 = s(1),e(1)
573     k1 = k2 + j1
574     kr = kr + 1
575     var(k1) = resh(kr)
576     ENDDO
577    
578    
579     ENDDO
580     ENDDO
581     ENDDO
582     ENDDO
583     ENDDO
584     ENDDO
585 edhill 1.8
586     C Close the file
587 edhill 1.9 CALL MNC_FILE_CLOSE(fname, myThid)
588 edhill 1.1
589 edhill 1.6 C End the lbj,lbi loops
590 edhill 1.1 ENDDO
591     ENDDO
592    
593     _END_MASTER( myThid )
594    
595     RETURN
596     END
597    
598     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
599    
600     CEH3 ;;; Local Variables: ***
601     CEH3 ;;; mode:fortran ***
602     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22