/[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.41 - (show annotations) (download)
Thu May 22 08:29:59 2008 UTC (16 years ago) by mlosch
Branch: MAIN
Changes since 1.40: +16 -2 lines
replace a dmv(2) with a rmv(2) to have a real*4 parameter where we
need one; add some commented code

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.40 2006/08/22 03:15:46 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_BUFF.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, uniq_fnum, nfname, iseq
111 integer fid, idv, indvids, ndim, indf, err, nf
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_PATH) fname
119 character*(MNC_MAX_PATH) path_fname
120 character*(MNC_MAX_PATH) tmpnm
121 character*(MNC_MAX_PATH) bpath
122 REAL*8 dval, dvm(2)
123 REAL*4 rval, rvm(2)
124 INTEGER ival, ivm(2), irv
125 REAL*8 resh_d( MNC_MAX_BUFF )
126 REAL*4 resh_r( MNC_MAX_BUFF )
127 INTEGER resh_i( MNC_MAX_BUFF )
128 LOGICAL write_attributes, use_missing
129 #ifdef HAVE_STAT
130 integer ntotenc, ncenc, nbytes, fs_isdone
131 character*(200) cenc
132 integer ienc(200)
133 REAL*8 fsnu
134 #endif
135
136 C Functions
137 integer IFNBLNK, ILNBLNK
138
139 C Only do I/O if I am the master thread
140 _BEGIN_MASTER( myThid )
141
142 DO i = 1,MNC_MAX_PATH
143 bpath(i:i) = ' '
144 ENDDO
145
146 C Get the current index for the unlimited dimension from the file
147 C group (or base) name
148 fg1 = IFNBLNK(fbname)
149 fg2 = ILNBLNK(fbname)
150 CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
151 IF (indfg .LT. 1) THEN
152 write(msgbuf,'(3a)')
153 & 'MNC_CW_RX_W ERROR: file group name ''',
154 & fbname(fg1:fg2), ''' is not defined'
155 CALL print_error(msgbuf, mythid)
156 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
157 ENDIF
158 indu = mnc_cw_fgud(indfg)
159 iseq = mnc_cw_fgis(indfg)
160 C write(*,*) 'indu,iseq = ', indu, iseq
161
162 C Check that the Variable Type exists
163 nvf = IFNBLNK(vtype)
164 nvl = ILNBLNK(vtype)
165 CALL MNC_GET_IND(MNC_MAX_ID, vtype, mnc_cw_vname, indv, myThid)
166 IF (indv .LT. 1) THEN
167 write(msgbuf,'(3a)') 'MNC_CW_RX_W ERROR: vtype ''',
168 & vtype(nvf:nvl), ''' is not defined'
169 CALL print_error(msgbuf, mythid)
170 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
171 ENDIF
172 igrid = mnc_cw_vgind(indv)
173
174 C Set the bi,bj indicies
175 bis = bi
176 bie = bi
177 IF (bi .LT. 1) THEN
178 bis = 1
179 bie = nSx
180 ENDIF
181 bjs = bj
182 bje = bj
183 IF (bj .LT. 1) THEN
184 bjs = 1
185 bje = nSy
186 ENDIF
187
188 DO lbj = bjs,bje
189 DO lbi = bis,bie
190
191 #ifdef HAVE_STAT
192 fs_isdone = 0
193 #endif
194 10 CONTINUE
195
196 C Create the file name
197 CALL MNC_CW_GET_TILE_NUM(lbi,lbj, uniq_tnum, myThid)
198 fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
199 n1 = IFNBLNK(fbname)
200 n2 = ILNBLNK(fbname)
201
202 #ifdef MNC_WRITE_OLDNAMES
203
204 ntot = n2 - n1 + 1
205 fname(1:ntot) = fbname(n1:n2)
206 ntot = ntot + 1
207 fname(ntot:ntot) = '.'
208 IF ( mnc_use_name_ni0 ) THEN
209 write(fname((ntot+1):(ntot+17)),'(i10.10,a1,i6.6)')
210 & nIter0,'.',uniq_tnum
211 write(fname((ntot+18):(ntot+25)),'(a1,i4.4,a3)')
212 & '.', iseq, '.nc'
213 nfname = ntot + 25
214 ELSE
215 write(fname((ntot+1):(ntot+14)),'(i4.4,a1,i6.6,a3)')
216 & iseq,'.',uniq_tnum, '.nc'
217 nfname = ntot + 14
218 ENDIF
219
220 #else
221
222 CALL MNC_PSNCM(tmpnm, uniq_tnum, MNC_DEF_TMNC)
223 k = ILNBLNK(tmpnm)
224 IF ( mnc_cw_cit(1,mnc_cw_fgci(indfg)) .GT. -1 ) THEN
225 j = mnc_cw_cit(2,mnc_cw_fgci(indfg))
226 IF ( mnc_cw_fgis(indfg) .GT. j )
227 & j = mnc_cw_fgis(indfg)
228 write(fname,'(a,a1,i10.10,a2,a,a3)') fbname(n1:n2),
229 & '.', j, '.t', tmpnm(1:k), '.nc'
230 ELSEIF ( mnc_cw_cit(1,mnc_cw_fgci(indfg)) .EQ. -1 ) THEN
231 C Leave off the myIter value entirely
232 write(fname,'(a,a2,a,a3)') fbname(n1:n2), '.t',
233 & tmpnm(1:k),'.nc'
234 ELSE
235 C We have an error--bad flag value
236 write(msgbuf,'(4a)')
237 & 'MNC_CW_RX_W ERROR: bad mnc_cw_cit(1,...) ',
238 & 'flag value for base name ''', fbname(fg1:fg2),
239 & ''''
240 CALL print_error(msgbuf, mythid)
241 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
242 ENDIF
243 nfname = ILNBLNK(fname)
244
245 #endif
246
247 C Add the path to the file name
248 IF (mnc_use_outdir) THEN
249 path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
250 npath = ILNBLNK(mnc_out_path)
251 path_fname(1:npath) = mnc_out_path(1:npath)
252 path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
253 fname(1:MNC_MAX_PATH) = path_fname(1:MNC_MAX_PATH)
254 nfname = npath + nfname
255 ENDIF
256
257 C Append to an existing or create a new file
258 CALL MNC_CW_FILE_AORC(fname,indf, lbi,lbj,uniq_tnum, myThid)
259 fid = mnc_f_info(indf,2)
260
261 #ifdef HAVE_STAT
262 IF ((mnc_cw_fgig(indfg) .EQ. 1)
263 & .AND. (fs_isdone .EQ. 0)) THEN
264 C Decide whether to append to the existing or create a new
265 C file based on the byte count per unlimited dimension
266 ncenc = 70
267 cenc(1:26) = 'abcdefghijklmnopqrstuvwxyz'
268 cenc(27:52) = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
269 cenc(53:70) = '0123456789_.,+-=/~'
270 k = nfname
271 IF (k .GT. 200) k = 200
272 ntotenc = 0
273 DO i = 1,k
274 DO j = 1,ncenc
275 IF (fname(i:i) .EQ. cenc(j:j)) THEN
276 ntotenc = ntotenc + 1
277 ienc(ntotenc) = j
278 GOTO 20
279 ENDIF
280 ENDDO
281 20 CONTINUE
282 ENDDO
283 CALL mncfsize(ntotenc, ienc, nbytes)
284 IF (nbytes .GT. 0) THEN
285 CALL MNC_DIM_UNLIM_SIZE(fname, unlim_sz, myThid)
286 fsnu = (1.0 _d 0 + 1.0 _d 0 / DBLE(unlim_sz))
287 & * DBLE(nbytes)
288 IF (fsnu .GT. mnc_max_fsize) THEN
289 C Delete the now-full fname from the lookup tables since
290 C we are all done writing to it.
291 CALL MNC_FILE_CLOSE(fname, myThid)
292 indu = 1
293 mnc_cw_fgud(indfg) = 1
294
295 #ifdef MNC_WRITE_OLDNAMES
296 iseq = iseq + 1
297 mnc_cw_fgis(indfg) = iseq
298 #else
299 IF (mnc_cw_cit(1,mnc_cw_fgci(indfg)) .LT. 0) THEN
300 write(msgbuf,'(5a)')
301 & 'MNC_CW_RX_W ERROR: output file for base name ''',
302 & fbname(fg1:fg2), ''' is about to exceed the max ',
303 & 'file size and is NOT ALLOWED an iteration value ',
304 & 'within its file name'
305 CALL print_error(msgbuf, mythid)
306 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
307 ELSEIF (mnc_cw_cit(3,mnc_cw_fgci(indfg)) .LT. 0) THEN
308 write(msgbuf,'(5a)')
309 & 'MNC_CW_RX_W ERROR: output file for base name ''',
310 & fbname(fg1:fg2), ''' is about to exceed the max ',
311 & 'file size and no next-iter has been specified--',
312 & 'please see the MNC CITER functions'
313 CALL print_error(msgbuf, mythid)
314 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
315 ENDIF
316 mnc_cw_fgis(indfg) = mnc_cw_cit(3,mnc_cw_fgci(indfg))
317 C DO NOT BUMP THE CURRENT ITER FOR ALL FILES IN THIS CITER
318 C GROUP SINCE THIS IS ONLY GROWTH TO AVOID FILE SIZE
319 C LIMITS FOR THIS ONE BASENAME GROUP, NOT GROWTH OF THE
320 C ENTIRE CITER GROUP !!!
321 C mnc_cw_cit(2,mnc_cw_fgci(indfg))
322 C & = mnc_cw_cit(3,mnc_cw_fgci(indfg))
323 C mnc_cw_cit(3,mnc_cw_fgci(indfg)) = -1
324 #endif
325 fs_isdone = 1
326 GOTO 10
327
328 ENDIF
329 ENDIF
330 ENDIF
331 #endif /* HAVE_STAT */
332
333 C Ensure that all the NetCDF dimensions are defined and create a
334 C local copy of them
335 DO i = 1,9
336 dimnc(i) = 1
337 ENDDO
338 DO i = 1,mnc_cw_ndim(igrid)
339 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
340 dimnc(i) = -1
341 ELSE
342 dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
343 ENDIF
344
345 C Add the coordinate variables
346 CALL MNC_DIM_INIT_ALL_CV(fname,
347 & mnc_cw_dn(i,igrid), dimnc(i), 'Y', lbi,lbj, myThid)
348
349 ENDDO
350
351 C Ensure that the "grid" is defined
352 CALL MNC_GRID_INIT(fname, mnc_cw_gname(igrid),
353 & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)
354
355 C Ensure that the variable is defined
356 irv = 0
357 IF (stype(1:1) .EQ. 'D')
358 & CALL MNC_VAR_INIT_DBL(
359 & fname, mnc_cw_gname(igrid), vtype, irv, myThid)
360 IF (stype(1:1) .EQ. 'R')
361 & CALL MNC_VAR_INIT_REAL(
362 & fname, mnc_cw_gname(igrid), vtype, irv, myThid)
363 IF (stype(1:1) .EQ. 'I')
364 & CALL MNC_VAR_INIT_INT(
365 & fname, mnc_cw_gname(igrid), vtype, irv, myThid)
366
367 IF (irv .GT. 0) THEN
368 C Return value indicates that the variable did not previously
369 C exist in this file, so we need to write all the attributes
370 write_attributes = .TRUE.
371 ELSE
372 write_attributes = .FALSE.
373 ENDIF
374
375 DO i = 1,mnc_fv_ids(indf,1)
376 j = 2 + 3*(i - 1)
377 IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
378 idv = mnc_fv_ids(indf,j+1)
379 indvids = mnc_fd_ind(indf, mnc_f_info(indf,
380 & (mnc_fv_ids(indf,j+2) + 1)) )
381 GOTO 30
382 ENDIF
383 ENDDO
384 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_W ERROR: ',
385 & 'cannot reference variable ''', vtype, ''''
386 CALL print_error(msgbuf, mythid)
387 STOP 'ABNORMAL END: package MNC'
388 30 CONTINUE
389
390 C Check for bi,bj indicies
391 bidim = mnc_cw_vbij(1,indv)
392 bjdim = mnc_cw_vbij(2,indv)
393 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
394
395 C Set the dimensions for the in-memory array
396 ndim = mnc_cw_ndim(igrid)
397 k = mnc_cw_dims(1,igrid)
398 IF (k .GT. 0) THEN
399 p(1) = k
400 ELSE
401 p(1) = 1
402 ENDIF
403 DO i = 2,9
404 k = mnc_cw_dims(i,igrid)
405 IF (k .LT. 1) THEN
406 k = 1
407 ENDIF
408 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
409 p(i) = nSx * p(i-1)
410 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
411 p(i) = nSy * p(i-1)
412 ELSE
413 p(i) = k * p(i-1)
414 ENDIF
415 IF (offsets(i) .GT. 0) THEN
416 k = 1
417 p(i) = k * p(i-1)
418 ENDIF
419 ENDDO
420
421 C Set starting and ending indicies for the in-memory array and
422 C the unlimited dimension offset for the NetCDF array
423 DO i = 1,9
424 udo(i) = 0
425 s(i) = 1
426 e(i) = 1
427 IF (i .LE. ndim) THEN
428 s(i) = mnc_cw_is(i,igrid)
429 e(i) = mnc_cw_ie(i,igrid)
430 ENDIF
431 C Check for the unlimited dimension
432 IF ((i .EQ. ndim)
433 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
434 IF (indu .GT. 0) THEN
435 C Use the indu value
436 udo(i) = indu - 1
437 ELSEIF (indu .EQ. -1) THEN
438 C Append one to the current unlimited dim size
439 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
440 udo(i) = unlim_sz
441 ELSE
442 C Use the current unlimited dim size
443 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
444 udo(i) = unlim_sz - 1
445 ENDIF
446 ENDIF
447 ENDDO
448 IF (bidim .GT. 0) THEN
449 s(bidim) = lbi
450 e(bidim) = lbi
451 ENDIF
452 IF (bjdim .GT. 0) THEN
453 s(bjdim) = lbj
454 e(bjdim) = lbj
455 ENDIF
456
457 C Check the offsets
458 DO i = 1,9
459 IF (offsets(i) .GT. 0) THEN
460 udo(i) = udo(i) + offsets(i) - 1
461 s(i) = 1
462 e(i) = 1
463 ENDIF
464 ENDDO
465
466 IF (write_attributes) THEN
467 C Add the per-variable attributes
468 DO i = 1,mnc_cw_vnat(1,indv)
469 CALL MNC_VAR_ADD_ATTR_STR( fname, vtype,
470 & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv), myThid)
471 ENDDO
472 DO i = 1,mnc_cw_vnat(2,indv)
473 CALL MNC_VAR_ADD_ATTR_INT( fname, vtype,
474 & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv), myThid)
475 ENDDO
476 DO i = 1,mnc_cw_vnat(3,indv)
477 CALL MNC_VAR_ADD_ATTR_DBL( fname, vtype,
478 & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv), myThid)
479 ENDDO
480 ENDIF
481
482 C Handle missing values
483 use_missing = .FALSE.
484 IF (mnc_cw_vfmv(indv) .EQ. 0) THEN
485 use_missing = .FALSE.
486 ELSE
487 IF (mnc_cw_vfmv(indv) .EQ. 1) THEN
488 use_missing = .TRUE.
489 dvm(1) = mnc_def_dmv(1)
490 dvm(2) = mnc_def_dmv(2)
491 rvm(1) = mnc_def_rmv(1)
492 rvm(2) = mnc_def_rmv(2)
493 ivm(1) = mnc_def_imv(1)
494 ivm(2) = mnc_def_imv(2)
495 ELSEIF (mnc_cw_vfmv(indv) .EQ. 2) THEN
496 use_missing = .TRUE.
497 dvm(1) = mnc_cw_vmvd(1,indv)
498 dvm(2) = mnc_cw_vmvd(2,indv)
499 rvm(1) = mnc_cw_vmvr(1,indv)
500 rvm(2) = mnc_cw_vmvr(2,indv)
501 ivm(1) = mnc_cw_vmvi(1,indv)
502 ivm(2) = mnc_cw_vmvi(2,indv)
503 ENDIF
504 ENDIF
505 IF (write_attributes .AND. use_missing) THEN
506 write(msgbuf,'(4a)') 'writing attribute ''missing_value''',
507 & ' within file ''', fname(1:nfname), ''''
508 IF (stype(1:1) .EQ. 'D') THEN
509 err = NF_PUT_ATT_DOUBLE(fid, idv, 'missing_value',
510 & NF_DOUBLE, 1, dvm(2))
511 ELSEIF (stype(1:1) .EQ. 'R') THEN
512 err = NF_PUT_ATT_REAL(fid, idv, 'missing_value',
513 & NF_FLOAT, 1, rvm(2))
514 ELSEIF (stype(1:1) .EQ. 'I') THEN
515 err = NF_PUT_ATT_INT(fid, idv, 'missing_value',
516 & NF_INT, 1, ivm(2))
517 ENDIF
518 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
519 CMLC it may be better to use the attribute _FillValue, or both
520 CML write(msgbuf,'(4a)') 'writing attribute ''_FillValue''',
521 CML & ' within file ''', fname(1:nfname), ''''
522 CML IF (stype(1:1) .EQ. 'D') THEN
523 CML err = NF_PUT_ATT_DOUBLE(fid, idv, '_FillValue',
524 CML & NF_DOUBLE, 1, dvm(2))
525 CML ELSEIF (stype(1:1) .EQ. 'R') THEN
526 CML err = NF_PUT_ATT_REAL(fid, idv, '_FillValue',
527 CML & NF_FLOAT, 1, rvm(2))
528 CML ELSEIF (stype(1:1) .EQ. 'I') THEN
529 CML err = NF_PUT_ATT_INT(fid, idv, '_FillValue',
530 CML & NF_INT, 1, ivm(2))
531 CML ENDIF
532 CML CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
533 ENDIF
534
535 CALL MNC_FILE_ENDDEF(fname, myThid)
536
537 write(msgbuf,'(5a)') 'writing variable type ''',
538 & vtype(nvf:nvl), ''' within file ''',
539 & fname(1:nfname), ''''
540
541 C DO i = 1,9
542 C write(*,*) 'i,p(i),s(i),e(i),udo(i),offsets(i) = ',
543 C & i,p(i),s(i),e(i),udo(i),offsets(i)
544 C ENDDO
545
546 C Write the variable one vector at a time
547 DO j7 = s(7),e(7)
548 k7 = (j7 - 1)*p(6)
549 vstart(7) = udo(7) + j7 - s(7) + 1
550 vcount(7) = 1
551 DO j6 = s(6),e(6)
552 k6 = (j6 - 1)*p(5) + k7
553 vstart(6) = udo(6) + j6 - s(6) + 1
554 vcount(6) = 1
555 DO j5 = s(5),e(5)
556 k5 = (j5 - 1)*p(4) + k6
557 vstart(5) = udo(5) + j5 - s(5) + 1
558 vcount(5) = 1
559 DO j4 = s(4),e(4)
560 k4 = (j4 - 1)*p(3) + k5
561 vstart(4) = udo(4) + j4 - s(4) + 1
562 vcount(4) = 1
563 DO j3 = s(3),e(3)
564 k3 = (j3 - 1)*p(2) + k4
565 vstart(3) = udo(3) + j3 - s(3) + 1
566 vcount(3) = 1
567 DO j2 = s(2),e(2)
568 k2 = (j2 - 1)*p(1) + k3
569 vstart(2) = udo(2) + j2 - s(2) + 1
570 vcount(2) = 1
571
572 kr = 0
573 vstart(1) = udo(1) + 1
574 vcount(1) = e(1) - s(1) + 1
575
576 IF (vcount(1) .GT. MNC_MAX_BUFF) THEN
577 write(msgbuf,'(2a,I7,a)') 'MNC_MAX_BUFF is too small',
578 & '--please increase to at least ',
579 & vcount(1), ' in ''MNC_BUFF.h'''
580 CALL PRINT_ERROR(msgBuf , 1)
581 STOP 'ABNORMAL END: S/R MNC_CW_RX_W_OFFSET'
582 ENDIF
583
584 IF (use_missing) THEN
585
586 IF (stype(1:1) .EQ. 'D') THEN
587 DO j1 = s(1),e(1)
588 k1 = k2 + j1
589 kr = kr + 1
590 dval = var(k1)
591 IF (dval .EQ. dvm(1)) THEN
592 resh_d(kr) = dvm(2)
593 ELSE
594 resh_d(kr) = dval
595 ENDIF
596 ENDDO
597 err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
598 ELSEIF (stype(1:1) .EQ. 'R') THEN
599 DO j1 = s(1),e(1)
600 k1 = k2 + j1
601 kr = kr + 1
602 rval = var(k1)
603 IF (rval .EQ. rvm(1)) THEN
604 resh_r(kr) = rvm(2)
605 ELSE
606 resh_r(kr) = rval
607 ENDIF
608 ENDDO
609 err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh_r)
610 ELSEIF (stype(1:1) .EQ. 'I') THEN
611 DO j1 = s(1),e(1)
612 k1 = k2 + j1
613 kr = kr + 1
614 ival = MNC2I( var(k1) )
615 IF (ival .EQ. ivm(1)) THEN
616 resh_i(kr) = ivm(2)
617 ELSE
618 resh_i(kr) = ival
619 ENDIF
620 ENDDO
621 err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh_i)
622 ENDIF
623
624 ELSE
625
626 IF (stype(1:1) .EQ. 'D') THEN
627 DO j1 = s(1),e(1)
628 k1 = k2 + j1
629 kr = kr + 1
630 resh_d(kr) = var(k1)
631 ENDDO
632 err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
633 ELSEIF (stype(1:1) .EQ. 'R') THEN
634 DO j1 = s(1),e(1)
635 k1 = k2 + j1
636 kr = kr + 1
637 resh_r(kr) = var(k1)
638 ENDDO
639 err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh_r)
640 ELSEIF (stype(1:1) .EQ. 'I') THEN
641 DO j1 = s(1),e(1)
642 k1 = k2 + j1
643 kr = kr + 1
644 resh_i(kr) = MNC2I( var(k1) )
645 ENDDO
646 err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh_i)
647 ENDIF
648
649 ENDIF
650 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
651
652 ENDDO
653 ENDDO
654 ENDDO
655 ENDDO
656 ENDDO
657 ENDDO
658
659 C Sync the file
660 err = NF_SYNC(fid)
661 nf = ILNBLNK( fname )
662 write(msgbuf,'(3a)') 'sync for file ''', fname(1:nf),
663 & ''' in S/R MNC_CW_RX_W'
664 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
665
666 ENDDO
667 ENDDO
668
669 _END_MASTER( myThid )
670
671 RETURN
672 END
673
674
675 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
676 CBOP 0
677 C !ROUTINE: MNC_CW_RX_R_S
678
679 C !INTERFACE:
680 SUBROUTINE MNC_CW_RX_R_S(
681 I stype,
682 I fbname, bi,bj,
683 I vtype,
684 I var,
685 I myThid )
686
687 C !DESCRIPTION:
688 C A scalar version of MNC_CW_RX_R() for compilers that cannot
689 C gracefully handle the conversion on their own.
690
691 C !USES:
692 implicit none
693
694 C !INPUT PARAMETERS:
695 integer myThid, bi,bj
696 character*(*) stype, fbname, vtype
697 __V var
698 __V var_arr(1)
699 CEOP
700 var_arr(1) = var
701
702 CALL MNC_CW_RX_R(stype,fbname,bi,bj,vtype, var_arr, myThid)
703
704 RETURN
705 END
706
707
708 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
709 CBOP 0
710 C !ROUTINE: MNC_CW_RX_R
711
712 C !INTERFACE:
713 SUBROUTINE MNC_CW_RX_R(
714 I stype,
715 I fbname, bi,bj,
716 I vtype,
717 I var,
718 I myThid )
719
720 C !DESCRIPTION:
721 C A simple wrapper for the old version of this routine. The new
722 C version includes the isvar argument which, for backwards
723 C compatibility, is set to false here.
724
725 C !USES:
726 implicit none
727
728 C !INPUT PARAMETERS:
729 integer myThid, bi,bj
730 character*(*) stype, fbname, vtype
731 __V var(*)
732 CEOP
733
734 C !LOCAL VARIABLES:
735 LOGICAL isvar
736
737 isvar = .FALSE.
738
739 CALL MNC_CW_RX_R_TF(stype,fbname,bi,bj,vtype,var,isvar,myThid)
740
741 RETURN
742 END
743
744
745 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
746 CBOP 0
747 C !ROUTINE: MNC_CW_RX_R
748
749 C !INTERFACE:
750 SUBROUTINE MNC_CW_RX_R_TF(
751 I stype,
752 I fbname, bi,bj,
753 I vtype,
754 I var,
755 B isvar,
756 I myThid )
757
758 C !DESCRIPTION:
759 C This subroutine reads one variable from a file or a file group,
760 C depending upon the tile indicies. If isvar is true and the
761 C variable does not exist, then isvar is set to false and the
762 C program continues normally. This allows one to gracefully handle
763 C the case of reading variables that might or might not exist.
764
765 C !USES:
766 implicit none
767 #include "netcdf.inc"
768 #include "mnc_common.h"
769 #include "SIZE.h"
770 #include "MNC_BUFF.h"
771 #include "EEPARAMS.h"
772 #include "PARAMS.h"
773 #include "MNC_PARAMS.h"
774
775 C !INPUT PARAMETERS:
776 integer myThid, bi,bj
777 character*(*) stype, fbname, vtype
778 __V var(*)
779 LOGICAL isvar
780 CEOP
781
782 C !LOCAL VARIABLES:
783 integer i,k, nvf,nvl, n1,n2, igrid, ntot, indu
784 integer bis,bie, bjs,bje, uniq_tnum,uniq_fnum, nfname, fid, idv
785 integer ndim, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
786 integer ind_vt, npath, unlid, f_or_t, ixoff,iyoff
787 C integer f_sNx,f_sNy, alen, atype, ind_fv_ids, ierr, indf
788 integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)
789 integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
790 character*(MAX_LEN_MBUF) msgbuf
791 character*(MNC_MAX_PATH) fname
792 character*(MNC_MAX_PATH) fname_zs
793 character*(MNC_MAX_PATH) tmpnm
794 character*(MNC_MAX_PATH) path_fname
795 character*(MNC_MAX_PATH) bpath
796 integer indfg, fg1,fg2
797 REAL*8 resh_d( MNC_MAX_BUFF )
798 REAL*4 resh_r( MNC_MAX_BUFF )
799 INTEGER resh_i( MNC_MAX_BUFF )
800
801 C Functions
802 integer IFNBLNK, ILNBLNK
803
804 C Only do I/O if I am the master thread
805 _BEGIN_MASTER( myThid )
806
807 DO i = 1,MNC_MAX_PATH
808 bpath(i:i) = ' '
809 ENDDO
810
811 C Get the current index for the unlimited dimension from the file
812 C group (or base) name
813 fg1 = IFNBLNK(fbname)
814 fg2 = ILNBLNK(fbname)
815 CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
816 IF (indfg .LT. 1) THEN
817 write(msgbuf,'(3a)')
818 & 'MNC_CW_RX_W ERROR: file group name ''',
819 & fbname(fg1:fg2), ''' is not defined'
820 CALL print_error(msgbuf, mythid)
821 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
822 ENDIF
823 indu = mnc_cw_fgud(indfg)
824
825 C Check that the Variable Type exists
826 nvf = IFNBLNK(vtype)
827 nvl = ILNBLNK(vtype)
828 CALL MNC_GET_IND( MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt, myThid)
829 IF (ind_vt .LT. 1) THEN
830 write(msgbuf,'(3a)') 'MNC_CW_RX_R ERROR: vtype ''',
831 & vtype(nvf:nvl), ''' is not defined'
832 CALL print_error(msgbuf, mythid)
833 STOP 'ABNORMAL END: S/R MNC_CW_RX_R'
834 ENDIF
835 igrid = mnc_cw_vgind(ind_vt)
836
837 C Check for bi,bj indicies
838 bidim = mnc_cw_vbij(1,ind_vt)
839 bjdim = mnc_cw_vbij(2,ind_vt)
840
841 C Set the bi,bj indicies
842 bis = bi
843 bie = bi
844 IF (bi .LT. 1) THEN
845 bis = 1
846 bie = nSx
847 ENDIF
848 bjs = bj
849 bje = bj
850 IF (bj .LT. 1) THEN
851 bjs = 1
852 bje = nSy
853 ENDIF
854
855 DO lbj = bjs,bje
856 DO lbi = bis,bie
857
858 C Create the file name
859 CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)
860 fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
861
862 #ifdef MNC_READ_OLDNAMES
863
864 n1 = IFNBLNK(fbname)
865 n2 = ILNBLNK(fbname)
866 ntot = n2 - n1 + 1
867 fname(1:ntot) = fbname(n1:n2)
868 ntot = ntot + 1
869 fname(ntot:ntot) = '.'
870 write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
871 nfname = ntot+9
872
873 C Add the path to the file name
874 IF (mnc_use_indir) THEN
875 path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
876 npath = ILNBLNK(mnc_indir_str)
877 path_fname(1:npath) = mnc_indir_str(1:npath)
878 path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
879 fname(1:MNC_MAX_PATH) = path_fname(1:MNC_MAX_PATH)
880 nfname = npath + nfname
881 ENDIF
882
883 WRITE(fname_zs,'(2a,i4.4,a1,i6.6,a3)')
884 & mnc_indir_str(1:npath), fbname(n1:n2),
885 & 0, '.', uniq_tnum, '.nc'
886
887 C The steps are:
888 C (1) open the file in a READ-ONLY mode,
889 C (2) get the var id for the current variable,
890 C (3) read the data, and then
891 C (4) close the file--theres no need to keep it open!
892
893 write(msgbuf,'(4a)') 'MNC_CW_RX_R: cannot open',
894 & ' file ''', fname(1:nfname), ''' in read-only mode'
895 err = NF_OPEN(fname, NF_NOWRITE, fid)
896 IF ( err .NE. NF_NOERR ) THEN
897 C If the initial open fails, try again using a name with a
898 C zero sequence number inserted
899 err = NF_OPEN(fname_zs, NF_NOWRITE, fid)
900 ENDIF
901 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
902
903 write(msgbuf,'(5a)')
904 & 'MNC_CW_RX_R: cannot get id for variable ''',
905 & vtype(nvf:nvl), '''in file ''', fname(1:nfname), ''''
906 err = NF_INQ_VARID(fid, vtype, idv)
907 IF ( isvar .AND. ( err .NE. NF_NOERR ) ) THEN
908 isvar = .FALSE.
909 RETURN
910 ENDIF
911 isvar = .TRUE.
912 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
913 f_or_t = 0
914
915 #else
916
917 C The sequence for PER-FACE and PER-TILE is:
918 C (1) check whether a PER-FACE file exists
919 C . (a) if only one face is used for the entire domain,
920 C . then omit the face index from the file name
921 C . (b) if the PER-FACE file exists and is somehow faulty,
922 C . then we die with an error message
923 C (2) if no PER-FACE file exists, then use a PER-TILE file
924
925 C Create the PER-FACE file name
926 n1 = IFNBLNK(fbname)
927 n2 = ILNBLNK(fbname)
928 C Add an iteraton count to the file name if its requested
929 IF (mnc_cw_cit(1,mnc_cw_fgci(indfg)) .LT. 0) THEN
930 WRITE(fname,'(a,a1)') fbname(n1:n2), '.'
931 ELSE
932 WRITE(fname,'(a,a1,i10.10,a1)') fbname(n1:n2), '.',
933 & mnc_cw_cit(2,mnc_cw_fgci(indfg)), '.'
934 ENDIF
935 ntot = ILNBLNK(fname)
936 path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
937 npath = ILNBLNK(mnc_indir_str)
938 C Add the face index
939 CALL MNC_CW_GET_FACE_NUM( lbi,lbj, uniq_fnum, myThid)
940 IF ( uniq_fnum .EQ. -1 ) THEN
941 C There is only one face
942 WRITE(path_fname,'(2a,a2)')
943 & mnc_indir_str(1:npath), fname(1:ntot), 'nc'
944 ELSE
945 CALL MNC_PSNCM(tmpnm, uniq_fnum, MNC_DEF_FMNC)
946 k = ILNBLNK(tmpnm)
947 WRITE(path_fname,'(2a,a1,a,a3)')
948 & mnc_indir_str(1:npath), fname(1:ntot), 'f',
949 & tmpnm(1:k), '.nc'
950 ENDIF
951
952 C Try to open the PER-FACE file
953 C WRITE(*,*) 'trying: "', path_fname, '"'
954 err = NF_OPEN(path_fname, NF_NOWRITE, fid)
955 IF ( err .EQ. NF_NOERR ) THEN
956 f_or_t = 1
957 ELSE
958
959 C Create the PER-TILE file name
960 CALL MNC_PSNCM(tmpnm, uniq_tnum, MNC_DEF_TMNC)
961 k = ILNBLNK(tmpnm)
962 path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
963 WRITE(path_fname,'(2a,a1,a,a3)')
964 & mnc_indir_str(1:npath), fname(1:ntot), 't',
965 & tmpnm(1:k), '.nc'
966 C WRITE(*,*) 'trying: "', path_fname, '"'
967 err = NF_OPEN(path_fname, NF_NOWRITE, fid)
968 IF ( err .EQ. NF_NOERR ) THEN
969 f_or_t = 0
970 ELSE
971 k = ILNBLNK(path_fname)
972 write(msgbuf,'(4a)')
973 & 'MNC_CW_RX_R: cannot open either a per-face or a ',
974 & 'per-tile file: last try was ''', path_fname(1:k),
975 & ''''
976 CALL print_error(msgbuf, mythid)
977 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
978 ENDIF
979
980 ENDIF
981
982 ntot = ILNBLNK(path_fname)
983 write(msgbuf,'(5a)')
984 & 'MNC_CW_RX_R: cannot get netCDF id for variable ''',
985 & vtype(nvf:nvl), ''' in file ''', path_fname(1:ntot),
986 & ''''
987 err = NF_INQ_VARID(fid, vtype, idv)
988 IF ( isvar .AND. ( err .NE. NF_NOERR ) ) THEN
989 isvar = .FALSE.
990 RETURN
991 ENDIF
992 isvar = .TRUE.
993 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
994
995 k = ILNBLNK(path_fname)
996 fname(1:k) = path_fname(1:k)
997 nfname = k
998
999 #endif
1000
1001 IF ( f_or_t .EQ. 1 ) THEN
1002
1003 C write(msgbuf,'(2a)')
1004 C & 'MNC_CW_RX_R: per-face reads are not yet ',
1005 C & 'implemented -- so pester Ed to finish them'
1006 C CALL print_error(msgbuf, mythid)
1007 C STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
1008
1009 C Get the X,Y PER-FACE offsets
1010 CALL MNC_CW_GET_XYFO(lbi,lbj, ixoff,iyoff, myThid)
1011
1012 ENDIF
1013
1014 C WRITE(*,*) 'f_or_t = ',f_or_t
1015
1016 C Check that the current sNy,sNy values and the in-file values
1017 C are compatible and WARN (only warn) if not
1018 C f_sNx = -1
1019 C f_sNy = -1
1020 C err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNx',atype,alen)
1021 C IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
1022 C err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', f_sNx)
1023 C CALL MNC_HANDLE_ERR(err,
1024 C & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R',
1025 C & myThid)
1026 C ENDIF
1027 C err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNy',atype,alen)
1028 C IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
1029 C err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', f_sNy)
1030 C CALL MNC_HANDLE_ERR(err,
1031 C & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R',
1032 C & myThid)
1033 C ENDIF
1034 C IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
1035 C write(msgbuf,'(5a)') 'MNC_CW_RX_R WARNING: the ',
1036 C & 'attributes ''sNx'' and ''sNy'' within the file ''',
1037 C & fname(1:nfname), ''' do not exist or do not match ',
1038 C & 'the current sizes within the model'
1039 C CALL print_error(msgbuf, mythid)
1040 C ENDIF
1041
1042 C Check that the in-memory variable and the in-file variables
1043 C are of compatible sizes
1044 C ires = 1
1045 C CALL MNC_CHK_VTYP_R_NCVAR( ind_vt,
1046 C & indf, ind_fv_ids, indu, ires)
1047 C IF (ires .LT. 0) THEN
1048 C write(msgbuf,'(7a)') 'MNC_CW_RX_R WARNING: the sizes ',
1049 C & 'of the in-program variable ''', vtype(nvf:nvl),
1050 C & ''' and the corresponding variable within file ''',
1051 C & fname(1:nfname), ''' are not compatible -- please ',
1052 C & 'check the sizes'
1053 C CALL print_error(msgbuf, mythid)
1054 C STOP 'ABNORMAL END: S/R MNC_CW_RX_R'
1055 C ENDIF
1056
1057 C Check for bi,bj indicies
1058 bidim = mnc_cw_vbij(1,ind_vt)
1059 bjdim = mnc_cw_vbij(2,ind_vt)
1060
1061 C Set the dimensions for the in-memory array
1062 ndim = mnc_cw_ndim(igrid)
1063 k = mnc_cw_dims(1,igrid)
1064 IF (k .GT. 0) THEN
1065 p(1) = k
1066 ELSE
1067 p(1) = 1
1068 ENDIF
1069 DO i = 2,9
1070 k = mnc_cw_dims(i,igrid)
1071 IF (k .LT. 1) THEN
1072 k = 1
1073 ENDIF
1074 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
1075 p(i) = nSx * p(i-1)
1076 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
1077 p(i) = nSy * p(i-1)
1078 ELSE
1079 p(i) = k * p(i-1)
1080 ENDIF
1081 ENDDO
1082
1083 C Set starting and ending indicies for the in-memory array and
1084 C the unlimited dimension offset for the NetCDF array
1085 DO i = 1,9
1086 udo(i) = 0
1087 s(i) = 1
1088 e(i) = 1
1089 IF (i .LE. ndim) THEN
1090 s(i) = mnc_cw_is(i,igrid)
1091 e(i) = mnc_cw_ie(i,igrid)
1092
1093 IF ( f_or_t .EQ. 1 ) THEN
1094 C Add the per-face X,Y offsets to the udo offset vector
1095 C since they accomplish the same thing
1096 IF ( mnc_cw_dn(i,igrid)(1:1) .EQ. 'X' ) THEN
1097 udo(i) = ixoff - 1
1098 ELSEIF ( mnc_cw_dn(i,igrid)(1:1) .EQ. 'Y' ) THEN
1099 udo(i) = iyoff - 1
1100 ENDIF
1101 ENDIF
1102
1103 ENDIF
1104 C Check for the unlimited dimension
1105 IF ((i .EQ. ndim)
1106 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
1107 IF (indu .GT. 0) THEN
1108 C Use the indu value
1109 udo(i) = indu - 1
1110 ELSE
1111 C We need the current unlim dim size
1112 write(msgbuf,'(5a)') 'MNC_CW_RX_R: getting the ',
1113 & 'unlim dim id within file ''',
1114 & fname(1:nfname), ''''
1115 err = NF_INQ_UNLIMDIM(fid, unlid)
1116 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
1117 write(msgbuf,'(5a)') 'MNC_CW_RX_R: getting the ',
1118 & 'unlim dim size within file ''',
1119 & fname(1:nfname), ''''
1120 err = NF_INQ_DIMLEN(fid, unlid, unlim_sz)
1121 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
1122 udo(i) = unlim_sz
1123 ENDIF
1124 ENDIF
1125 ENDDO
1126 IF (bidim .GT. 0) THEN
1127 s(bidim) = lbi
1128 e(bidim) = lbi
1129 ENDIF
1130 IF (bjdim .GT. 0) THEN
1131 s(bjdim) = lbj
1132 e(bjdim) = lbj
1133 ENDIF
1134
1135 C DO i = 9,1,-1
1136 C write(*,*) 'i,p(i),s(i),e(i) = ', i,': ',p(i),s(i),e(i)
1137 C ENDDO
1138
1139 write(msgbuf,'(5a)') 'reading variable type ''',
1140 & vtype(nvf:nvl), ''' within file ''',
1141 & fname(1:nfname), ''''
1142
1143 C Read the variable one vector at a time
1144 DO j7 = s(7),e(7)
1145 k7 = (j7 - 1)*p(6)
1146 vstart(7) = udo(7) + j7 - s(7) + 1
1147 vcount(7) = 1
1148 DO j6 = s(6),e(6)
1149 k6 = (j6 - 1)*p(5) + k7
1150 vstart(6) = udo(6) + j6 - s(6) + 1
1151 vcount(6) = 1
1152 DO j5 = s(5),e(5)
1153 k5 = (j5 - 1)*p(4) + k6
1154 vstart(5) = udo(5) + j5 - s(5) + 1
1155 vcount(5) = 1
1156 DO j4 = s(4),e(4)
1157 k4 = (j4 - 1)*p(3) + k5
1158 vstart(4) = udo(4) + j4 - s(4) + 1
1159 vcount(4) = 1
1160 DO j3 = s(3),e(3)
1161 k3 = (j3 - 1)*p(2) + k4
1162 vstart(3) = udo(3) + j3 - s(3) + 1
1163 vcount(3) = 1
1164 DO j2 = s(2),e(2)
1165 k2 = (j2 - 1)*p(1) + k3
1166 vstart(2) = udo(2) + j2 - s(2) + 1
1167 vcount(2) = 1
1168
1169 kr = 0
1170 vstart(1) = udo(1) + 1
1171 vcount(1) = e(1) - s(1) + 1
1172
1173 IF (vcount(1) .GT. MNC_MAX_BUFF) THEN
1174 write(msgbuf,'(2a,I7,a)') 'MNC_MAX_BUFF is too small',
1175 & '--please increase to at least ',
1176 & vcount(1), ' in ''MNC_BUFF.h'''
1177 CALL PRINT_ERROR(msgBuf , 1)
1178 STOP 'ABNORMAL END: S/R MNC_CW_RX_R_OFFSET'
1179 ENDIF
1180
1181 IF (stype(1:1) .EQ. 'D') THEN
1182 err = NF_GET_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
1183 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
1184 DO j1 = s(1),e(1)
1185 k1 = k2 + j1
1186 kr = kr + 1
1187 var(k1) = MNCI2( resh_d(kr) )
1188 ENDDO
1189 ENDIF
1190 IF (stype(1:1) .EQ. 'R') THEN
1191 err = NF_GET_VARA_REAL(fid, idv, vstart, vcount, resh_r)
1192 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
1193 DO j1 = s(1),e(1)
1194 k1 = k2 + j1
1195 kr = kr + 1
1196 var(k1) = MNCI2( resh_r(kr) )
1197 ENDDO
1198 ENDIF
1199 IF (stype(1:1) .EQ. 'I') THEN
1200 err = NF_GET_VARA_INT(fid, idv, vstart, vcount, resh_i)
1201 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
1202 DO j1 = s(1),e(1)
1203 k1 = k2 + j1
1204 kr = kr + 1
1205 var(k1) = resh_i(kr)
1206 ENDDO
1207 ENDIF
1208
1209
1210 ENDDO
1211 ENDDO
1212 ENDDO
1213 ENDDO
1214 ENDDO
1215 ENDDO
1216
1217 C Close the file
1218 C CALL MNC_FILE_CLOSE(fname, myThid)
1219 err = NF_CLOSE(fid)
1220 write(msgbuf,'(3a)') 'MNC_CW_RX_R: cannot close file ''',
1221 & fname(1:nfname), ''''
1222 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
1223
1224
1225 C End the lbj,lbi loops
1226 ENDDO
1227 ENDDO
1228
1229 _END_MASTER( myThid )
1230
1231 RETURN
1232 END
1233
1234 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
1235
1236 CEH3 ;;; Local Variables: ***
1237 CEH3 ;;; mode:fortran ***
1238 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22