/[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.22 - (show annotations) (download)
Wed Oct 20 21:26:14 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
Changes since 1.21: +6 -4 lines
 o add a sequence number to the output file names in preparation for
   automatic handling of the 2GB NetCDF file size limitation

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

  ViewVC Help
Powered by ViewVC 1.1.22