/[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.11 - (show annotations) (download)
Mon Mar 22 05:10:10 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.10: +10 -4 lines
 o C code to create a directory (eg. "mnc_20040322_0001") with a name
   based on the creation date and a sequence number

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

  ViewVC Help
Powered by ViewVC 1.1.22