/[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.43 - (hide annotations) (download)
Thu Jan 21 01:48:05 2010 UTC (14 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62c, checkpoint62b, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, HEAD
Changes since 1.42: +123 -108 lines
remove unused variables

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

  ViewVC Help
Powered by ViewVC 1.1.22