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

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

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


Revision 1.17 - (show annotations) (download)
Fri Apr 2 16:12:48 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint54b_post, checkpoint53b_pre, checkpoint54d_post, checkpoint52m_post, checkpoint53a_post, checkpoint54, checkpoint53b_post, checkpoint53, checkpoint53g_post, checkpoint53f_post, checkpoint53d_pre, checkpoint54c_post
Changes since 1.16: +8 -7 lines
 o more comments for the api_reference (protex)

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

  ViewVC Help
Powered by ViewVC 1.1.22