/[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.25 - (show annotations) (download)
Sun Nov 14 03:34:35 2004 UTC (19 years, 6 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint56b_post, checkpoint56c_post, checkpoint57a_post, checkpoint57a_pre, checkpoint57, checkpoint56, checkpoint56a_post
Changes since 1.24: +4 -1 lines
 o if file capacity is reached, close it and empty it from the lookup
   tables

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

  ViewVC Help
Powered by ViewVC 1.1.22