/[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.10 - (show annotations) (download)
Sun Mar 21 03:44:23 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
Changes since 1.9: +34 -4 lines
 o finish implementation of the separate unlimited-dim handling for the
   MNC_CW_*_R_* and MNC_CW_*_W_* functions

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

  ViewVC Help
Powered by ViewVC 1.1.22