/[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.32 - (hide annotations) (download)
Sat Sep 10 18:30:07 2005 UTC (18 years, 9 months ago) by edhill
Branch: MAIN
Changes since 1.31: +167 -10 lines
 o various changes to mnc including:
   - all files use the new "BASENAME[[.ITER].{t|f}NUM].nc" format
   - output can now be grouped so that all files within a group
       change the ITER portion of their names in lock-step together
   - can now read ("global") PER-FACE (in addition to PER-TILE) files
       and works with both EXCH1 and EXCH2 (but needs more testing)
   - writing works for all verification test cases w/ g77 on Linux

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

  ViewVC Help
Powered by ViewVC 1.1.22