/[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.13 - (show annotations) (download)
Wed Mar 24 03:38:50 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.12: +17 -5 lines
 o fix off-by-one indexing error

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

  ViewVC Help
Powered by ViewVC 1.1.22