/[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.30 - (show annotations) (download)
Fri Jun 24 19:43:52 2005 UTC (18 years, 10 months ago) by edhill
Branch: MAIN
Changes since 1.29: +16 -18 lines
 o when reading with MNC, first try a file name without a sequence
   number and, if that fails, then try adding a '.0000' sequence number
   to the file name
   - requested by Baylor and Daniel

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.29 2005/02/28 17:53:29 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, lbi,lbj,uniq_tnum, 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
217 C file 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
267 C Add the coordinate variables
268 CALL MNC_DIM_INIT_ALL_CV(fname,
269 & mnc_cw_dn(i,igrid), dimnc(i), 'Y', lbi,lbj, myThid)
270
271 ENDDO
272
273 C Ensure that the "grid" is defined
274 CALL MNC_GRID_INIT(fname, mnc_cw_gname(igrid),
275 & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)
276
277 C Ensure that the variable is defined
278 IF (stype(1:1) .EQ. 'D')
279 & CALL MNC_VAR_INIT_DBL(
280 & fname, mnc_cw_gname(igrid), vtype, myThid)
281 IF (stype(1:1) .EQ. 'R')
282 & CALL MNC_VAR_INIT_REAL(
283 & fname, mnc_cw_gname(igrid), vtype, myThid)
284 IF (stype(1:1) .EQ. 'I')
285 & CALL MNC_VAR_INIT_INT(
286 & fname, mnc_cw_gname(igrid), vtype, myThid)
287
288 DO i = 1,mnc_fv_ids(indf,1)
289 j = 2 + 3*(i - 1)
290 IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
291 idv = mnc_fv_ids(indf,j+1)
292 indvids = mnc_fd_ind(indf, mnc_f_info(indf,
293 & (mnc_fv_ids(indf,j+2) + 1)) )
294 GOTO 30
295 ENDIF
296 ENDDO
297 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_W ERROR: ',
298 & 'cannot reference variable ''', vtype, ''''
299 CALL print_error(msgbuf, mythid)
300 STOP 'ABNORMAL END: package MNC'
301 30 CONTINUE
302
303 C Check for bi,bj indicies
304 bidim = mnc_cw_vbij(1,indv)
305 bjdim = mnc_cw_vbij(2,indv)
306 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
307
308 C Set the dimensions for the in-memory array
309 ndim = mnc_cw_ndim(igrid)
310 k = mnc_cw_dims(1,igrid)
311 IF (k .GT. 0) THEN
312 p(1) = k
313 ELSE
314 p(1) = 1
315 ENDIF
316 DO i = 2,9
317 k = mnc_cw_dims(i,igrid)
318 IF (k .LT. 1) THEN
319 k = 1
320 ENDIF
321 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
322 p(i) = nSx * p(i-1)
323 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
324 p(i) = nSy * p(i-1)
325 ELSE
326 p(i) = k * p(i-1)
327 ENDIF
328 IF (offsets(i) .GT. 0) THEN
329 k = 1
330 p(i) = k * p(i-1)
331 ENDIF
332 ENDDO
333
334 C Set starting and ending indicies for the in-memory array and
335 C the unlimited dimension offset for the NetCDF array
336 DO i = 1,9
337 udo(i) = 0
338 s(i) = 1
339 e(i) = 1
340 IF (i .LE. ndim) THEN
341 s(i) = mnc_cw_is(i,igrid)
342 e(i) = mnc_cw_ie(i,igrid)
343 ENDIF
344 C Check for the unlimited dimension
345 IF ((i .EQ. ndim)
346 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
347 IF (indu .GT. 0) THEN
348 C Use the indu value
349 udo(i) = indu - 1
350 ELSEIF (indu .EQ. -1) THEN
351 C Append one to the current unlimited dim size
352 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
353 udo(i) = unlim_sz
354 ELSE
355 C Use the current unlimited dim size
356 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
357 udo(i) = unlim_sz - 1
358 ENDIF
359 ENDIF
360 ENDDO
361 IF (bidim .GT. 0) THEN
362 s(bidim) = lbi
363 e(bidim) = lbi
364 ENDIF
365 IF (bjdim .GT. 0) THEN
366 s(bjdim) = lbj
367 e(bjdim) = lbj
368 ENDIF
369
370 C Check the offsets
371 DO i = 1,9
372 IF (offsets(i) .GT. 0) THEN
373 udo(i) = udo(i) + offsets(i) - 1
374 s(i) = 1
375 e(i) = 1
376 ENDIF
377 ENDDO
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) = MNC2I( 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, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
560 integer ind_vt, npath, unlid
561 C integer f_sNx,f_sNy, alen, atype, ind_fv_ids, ierr, indf
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) fname_zs
567 character*(MNC_MAX_CHAR) path_fname
568 integer indfg, fg1,fg2
569 REAL*8 resh_d( MNC_MAX_BUFF )
570 REAL*4 resh_r( MNC_MAX_BUFF )
571 INTEGER resh_i( MNC_MAX_BUFF )
572
573 C Functions
574 integer IFNBLNK, ILNBLNK
575
576 C Only do I/O if I am the master thread
577 _BEGIN_MASTER( myThid )
578
579 C Get the current index for the unlimited dimension from the file
580 C group (or base) name
581 fg1 = IFNBLNK(fbname)
582 fg2 = ILNBLNK(fbname)
583 CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
584 IF (indfg .LT. 1) THEN
585 write(msgbuf,'(3a)')
586 & 'MNC_CW_RX_W ERROR: file group name ''',
587 & fbname(fg1:fg2), ''' is not defined'
588 CALL print_error(msgbuf, mythid)
589 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
590 ENDIF
591 indu = mnc_cw_fgud(indfg)
592
593 C Check that the Variable Type exists
594 nvf = IFNBLNK(vtype)
595 nvl = ILNBLNK(vtype)
596 CALL MNC_GET_IND( MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt, myThid)
597 IF (ind_vt .LT. 1) THEN
598 write(msgbuf,'(3a)') 'MNC_CW_RX_R ERROR: vtype ''',
599 & vtype(nvf:nvl), ''' is not defined'
600 CALL print_error(msgbuf, mythid)
601 STOP 'ABNORMAL END: S/R MNC_CW_RX_R'
602 ENDIF
603 igrid = mnc_cw_vgind(ind_vt)
604
605 C Check for bi,bj indicies
606 bidim = mnc_cw_vbij(1,ind_vt)
607 bjdim = mnc_cw_vbij(2,ind_vt)
608
609 C Set the bi,bj indicies
610 bis = bi
611 bie = bi
612 IF (bi .LT. 1) THEN
613 bis = 1
614 bie = nSx
615 ENDIF
616 bjs = bj
617 bje = bj
618 IF (bj .LT. 1) THEN
619 bjs = 1
620 bje = nSy
621 ENDIF
622
623 DO lbj = bjs,bje
624 DO lbi = bis,bie
625
626 C Create the file name
627 CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)
628 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
629 n1 = IFNBLNK(fbname)
630 n2 = ILNBLNK(fbname)
631 ntot = n2 - n1 + 1
632 fname(1:ntot) = fbname(n1:n2)
633 ntot = ntot + 1
634 fname(ntot:ntot) = '.'
635 write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
636 nfname = ntot+9
637
638 C Add the path to the file name
639 IF (mnc_use_indir) THEN
640 path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
641 npath = ILNBLNK(mnc_indir_str)
642 path_fname(1:npath) = mnc_indir_str(1:npath)
643 path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
644 fname(1:MNC_MAX_CHAR) = path_fname(1:MNC_MAX_CHAR)
645 nfname = npath + nfname
646 ENDIF
647
648 WRITE(fname_zs,'(2a,i4.4,a1,i6.6,a3)')
649 & mnc_indir_str(1:npath), fbname(n1:n2),
650 & 0, '.', uniq_tnum, '.nc'
651
652 C The steps are:
653 C (1) open the file in a READ-ONLY mode,
654 C (2) get the var id for the current variable,
655 C (3) read the data, and then
656 C (4) close the file--theres no need to keep it open!
657
658 write(msgbuf,'(4a)') 'MNC_CW_RX_R: cannot open',
659 & ' file ''', fname(1:nfname), ''' in read-only mode'
660 err = NF_OPEN(fname, NF_NOWRITE, fid)
661 IF ( err .NE. NF_NOERR ) THEN
662 C If the initial open fails, try again using a name with a
663 C zero sequence number inserted
664 err = NF_OPEN(fname_zs, NF_NOWRITE, fid)
665 ENDIF
666 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
667
668 write(msgbuf,'(6a)')
669 & 'MNC_CW_RX_R: cannot get id for variable ''',
670 & vtype(nvf:nvl), '''in file ''', fname(1:nfname), ''''
671 err = NF_INQ_VARID(fid, vtype, idv)
672 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
673
674 C Check that the current sNy,sNy values and the in-file values
675 C are compatible and WARN (only warn) if not
676 C f_sNx = -1
677 C f_sNy = -1
678 C err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNx',atype,alen)
679 C IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
680 C err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', f_sNx)
681 C CALL MNC_HANDLE_ERR(err,
682 C & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R',
683 C & myThid)
684 C ENDIF
685 C err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNy',atype,alen)
686 C IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
687 C err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', f_sNy)
688 C CALL MNC_HANDLE_ERR(err,
689 C & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R',
690 C & myThid)
691 C ENDIF
692 C IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
693 C write(msgbuf,'(5a)') 'MNC_CW_RX_R WARNING: the ',
694 C & 'attributes ''sNx'' and ''sNy'' within the file ''',
695 C & fname(1:nfname), ''' do not exist or do not match ',
696 C & 'the current sizes within the model'
697 C CALL print_error(msgbuf, mythid)
698 C ENDIF
699
700 C Check that the in-memory variable and the in-file variables
701 C are of compatible sizes
702 C ires = 1
703 C CALL MNC_CHK_VTYP_R_NCVAR( ind_vt,
704 C & indf, ind_fv_ids, indu, ires)
705 C IF (ires .LT. 0) THEN
706 C write(msgbuf,'(7a)') 'MNC_CW_RX_R WARNING: the sizes ',
707 C & 'of the in-program variable ''', vtype(nvf:nvl),
708 C & ''' and the corresponding variable within file ''',
709 C & fname(1:nfname), ''' are not compatible -- please ',
710 C & 'check the sizes'
711 C CALL print_error(msgbuf, mythid)
712 C STOP 'ABNORMAL END: S/R MNC_CW_RX_R'
713 C ENDIF
714
715 C Check for bi,bj indicies
716 bidim = mnc_cw_vbij(1,ind_vt)
717 bjdim = mnc_cw_vbij(2,ind_vt)
718
719 C Set the dimensions for the in-memory array
720 ndim = mnc_cw_ndim(igrid)
721 k = mnc_cw_dims(1,igrid)
722 IF (k .GT. 0) THEN
723 p(1) = k
724 ELSE
725 p(1) = 1
726 ENDIF
727 DO i = 2,9
728 k = mnc_cw_dims(i,igrid)
729 IF (k .LT. 1) THEN
730 k = 1
731 ENDIF
732 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
733 p(i) = nSx * p(i-1)
734 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
735 p(i) = nSy * p(i-1)
736 ELSE
737 p(i) = k * p(i-1)
738 ENDIF
739 ENDDO
740
741 C Set starting and ending indicies for the in-memory array and
742 C the unlimited dimension offset for the NetCDF array
743 DO i = 1,9
744 udo(i) = 0
745 s(i) = 1
746 e(i) = 1
747 IF (i .LE. ndim) THEN
748 s(i) = mnc_cw_is(i,igrid)
749 e(i) = mnc_cw_ie(i,igrid)
750 ENDIF
751 C Check for the unlimited dimension
752 IF ((i .EQ. ndim)
753 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
754 IF (indu .GT. 0) THEN
755 C Use the indu value
756 udo(i) = indu - 1
757 ELSE
758 C We need the current unlim dim size
759 write(msgbuf,'(5a)') 'MNC_CW_RX_R: getting the ',
760 & 'unlim dim id within file ''',
761 & fname(1:nfname), ''''
762 err = NF_INQ_UNLIMDIM(fid, unlid)
763 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
764 write(msgbuf,'(5a)') 'MNC_CW_RX_R: getting the ',
765 & 'unlim dim size within file ''',
766 & fname(1:nfname), ''''
767 err = NF_INQ_DIMLEN(fid, unlid, unlim_sz)
768 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
769 udo(i) = unlim_sz
770 ENDIF
771 ENDIF
772 ENDDO
773 IF (bidim .GT. 0) THEN
774 s(bidim) = lbi
775 e(bidim) = lbi
776 ENDIF
777 IF (bjdim .GT. 0) THEN
778 s(bjdim) = lbj
779 e(bjdim) = lbj
780 ENDIF
781
782 C DO i = 9,1,-1
783 C write(*,*) 'i,p(i),s(i),e(i) = ', i,': ',p(i),s(i),e(i)
784 C ENDDO
785
786 write(msgbuf,'(5a)') 'reading variable type ''',
787 & vtype(nvf:nvl), ''' within file ''',
788 & fname(1:nfname), ''''
789
790 C Read the variable one vector at a time
791 DO j7 = s(7),e(7)
792 k7 = (j7 - 1)*p(6)
793 vstart(7) = udo(7) + j7 - s(7) + 1
794 vcount(7) = 1
795 DO j6 = s(6),e(6)
796 k6 = (j6 - 1)*p(5) + k7
797 vstart(6) = udo(6) + j6 - s(6) + 1
798 vcount(6) = 1
799 DO j5 = s(5),e(5)
800 k5 = (j5 - 1)*p(4) + k6
801 vstart(5) = udo(5) + j5 - s(5) + 1
802 vcount(5) = 1
803 DO j4 = s(4),e(4)
804 k4 = (j4 - 1)*p(3) + k5
805 vstart(4) = udo(4) + j4 - s(4) + 1
806 vcount(4) = 1
807 DO j3 = s(3),e(3)
808 k3 = (j3 - 1)*p(2) + k4
809 vstart(3) = udo(3) + j3 - s(3) + 1
810 vcount(3) = 1
811 DO j2 = s(2),e(2)
812 k2 = (j2 - 1)*p(1) + k3
813 vstart(2) = udo(2) + j2 - s(2) + 1
814 vcount(2) = 1
815
816 kr = 0
817 vstart(1) = udo(1) + 1
818 vcount(1) = e(1) - s(1) + 1
819
820 IF (vcount(1) .GT. MNC_MAX_BUFF) THEN
821 write(msgbuf,'(2a,I7,a)') 'MNC_MAX_BUFF is too small',
822 & '--please increase to at least ',
823 & vcount(1), ' in ''MNC_SIZE.h'''
824 CALL PRINT_ERROR(msgBuf , 1)
825 STOP 'ABNORMAL END: S/R MNC_CW_RX_R_OFFSET'
826 ENDIF
827
828 IF (stype(1:1) .EQ. 'D') THEN
829 err = NF_GET_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
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) = MNCI2( resh_d(kr) )
835 ENDDO
836 ENDIF
837 IF (stype(1:1) .EQ. 'R') THEN
838 err = NF_GET_VARA_REAL(fid, idv, vstart, vcount, resh_r)
839 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
840 DO j1 = s(1),e(1)
841 k1 = k2 + j1
842 kr = kr + 1
843 var(k1) = MNCI2( resh_r(kr) )
844 ENDDO
845 ENDIF
846 IF (stype(1:1) .EQ. 'I') THEN
847 err = NF_GET_VARA_INT(fid, idv, vstart, vcount, resh_i)
848 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
849 DO j1 = s(1),e(1)
850 k1 = k2 + j1
851 kr = kr + 1
852 var(k1) = resh_i(kr)
853 ENDDO
854 ENDIF
855
856
857 ENDDO
858 ENDDO
859 ENDDO
860 ENDDO
861 ENDDO
862 ENDDO
863
864 C Close the file
865 C CALL MNC_FILE_CLOSE(fname, myThid)
866 err = NF_CLOSE(fid)
867 write(msgbuf,'(3a)') 'MNC_CW_RX_R: cannot close file ''',
868 & fname(1:nfname), ''''
869 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
870
871
872 C End the lbj,lbi loops
873 ENDDO
874 ENDDO
875
876 _END_MASTER( myThid )
877
878 RETURN
879 END
880
881 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
882
883 CEH3 ;;; Local Variables: ***
884 CEH3 ;;; mode:fortran ***
885 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22