/[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.24 - (show annotations) (download)
Fri Oct 22 21:30:31 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint55j_post, checkpoint55i_post
Changes since 1.23: +26 -8 lines
 o fix internal buffer overrun and add check so it never happens again
   without a proper error message

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

  ViewVC Help
Powered by ViewVC 1.1.22