/[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.35 - (hide annotations) (download)
Fri Feb 24 20:39:10 2006 UTC (18 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.34: +136 -41 lines
add missing-value capability to MNC:
 + currently off by default for everything
 + compiles and runs with GNU, Intel, & PGI
 + includes code to skip attributes writing for all but the initial
     write of any variable within any netCDF file

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

  ViewVC Help
Powered by ViewVC 1.1.22