/[MITgcm]/MITgcm/pkg/mnc/mnc_cw_readwrite.template
ViewVC logotype

Annotation of /MITgcm/pkg/mnc/mnc_cw_readwrite.template

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.34 - (hide annotations) (download)
Sat Sep 24 03:44:54 2005 UTC (19 years ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57v_post, checkpoint57y_post, checkpoint57y_pre, checkpoint58, checkpoint57x_post, checkpoint57w_post, checkpint57u_post, checkpoint58a_post, checkpoint57z_post
Changes since 1.33: +13 -6 lines
 o fix the MNC file size limit bug reported by Steph today
   - thoroughly tested with dic_example
   - correctly does "per-file-basename" increments of the filename
       iteration numbers (when necessary due to the max file size
       limit) as as requested by JMC and CNH during our last [and
       hopefully final! ;-)] discussion of this issue a week ago

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

  ViewVC Help
Powered by ViewVC 1.1.22