/[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.12 - (hide annotations) (download)
Tue Mar 23 05:24:44 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
Changes since 1.11: +11 -7 lines
 o per AJA & JMC request, re-write the MNC directory creation code:
   - directory names (strings) are passed, encoded using integers
   - everything is run-time optional with flags in "data.mnc"
   - tested and works but would benefit from some cleanup

1 edhill 1.12 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.11 2004/03/22 05:10:10 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    
8 edhill 1.3 SUBROUTINE MNC_CW_RX_W_YY(
9 edhill 1.1 I fbname, bi,bj,
10     I vtype,
11 edhill 1.9 I var,
12     I myThid )
13 edhill 1.1
14     implicit none
15    
16     #include "netcdf.inc"
17     #include "mnc_common.h"
18 edhill 1.12 #include "SIZE.h"
19 edhill 1.1 #include "EEPARAMS.h"
20 edhill 1.12 #include "PARAMS.h"
21 edhill 1.2
22     #define mnc_rtype_YY
23 edhill 1.1
24     C Arguments
25     integer myThid, bi,bj, indu
26     character*(*) fbname, vtype
27 edhill 1.6 __V var(*)
28 edhill 1.1
29     C Functions
30     integer IFNBLNK, ILNBLNK
31    
32     C Local Variables
33 edhill 1.3 integer i,j,k, indv,nvf,nvl, n1,n2, igrid, ntot
34 edhill 1.2 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv, indvids
35 edhill 1.3 integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
36     integer p(9),s(9),e(9), dimnc(9), vstart(9),vcount(9), udo(9)
37     integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
38 edhill 1.11 integer indfg, fg1,fg2, npath
39 edhill 1.1 character*(MAX_LEN_MBUF) msgbuf
40     character*(MNC_MAX_CHAR) fname
41 edhill 1.11 character*(MNC_MAX_CHAR) path_fname
42 edhill 1.1
43     C Temporary storage for the simultaneous type conversion and
44     C re-shaping before passing to NetCDF
45     #ifdef mnc_rtype_D
46 edhill 1.6 REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
47 edhill 1.1 #endif
48     #ifdef mnc_rtype_R
49 edhill 1.6 REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
50     #endif
51     #ifdef mnc_rtype_I
52     INTEGER resh( sNx + 2*OLx + sNy + 2*OLy )
53 edhill 1.1 #endif
54    
55     C Only do I/O if I am the master thread
56     _BEGIN_MASTER( myThid )
57    
58 edhill 1.10 C Get the current index for the unlimited dimension from the file
59     C group (or base) name
60     fg1 = IFNBLNK(fbname)
61     fg2 = ILNBLNK(fbname)
62     CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
63     IF (indfg .LT. 1) THEN
64     write(msgbuf,'(3a)')
65     & 'MNC_CW_RX_W_YY ERROR: file group name ''',
66     & fbname(fg1:fg2), ''' is not defined'
67     CALL print_error(msgbuf, mythid)
68     STOP 'ABNORMAL END: S/R MNC_CW_RX_W_YY'
69     ENDIF
70     indu = mnc_cw_fgud(indfg)
71    
72 edhill 1.1 C Check that the Variable Type exists
73     nvf = IFNBLNK(vtype)
74     nvl = ILNBLNK(vtype)
75 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, vtype, mnc_cw_vname, indv, myThid)
76 edhill 1.2 IF (indv .LT. 1) THEN
77 edhill 1.6 write(msgbuf,'(3a)') 'MNC_CW_RX_W_YY ERROR: vtype ''',
78 edhill 1.2 & vtype(nvf:nvl), ''' is not defined'
79 edhill 1.1 CALL print_error(msgbuf, mythid)
80 edhill 1.6 STOP 'ABNORMAL END: S/R MNC_CW_RX_W_YY'
81 edhill 1.1 ENDIF
82 edhill 1.2 igrid = mnc_cw_vgind(indv)
83 edhill 1.1
84 edhill 1.5 C Set the bi,bj indicies
85 edhill 1.2 bis = bi
86     bie = bi
87 edhill 1.1 IF (bi .LT. 1) THEN
88     bis = 1
89     bie = nSx
90     ENDIF
91 edhill 1.2 bjs = bj
92     bje = bj
93 edhill 1.1 IF (bj .LT. 1) THEN
94     bjs = 1
95     bje = nSy
96     ENDIF
97    
98 edhill 1.2 DO lbj = bjs,bje
99     DO lbi = bis,bie
100 edhill 1.1
101     C Create the file name
102 edhill 1.9 CALL MNC_CW_GET_TILE_NUM(lbi,lbj, uniq_tnum, myThid)
103 edhill 1.1 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
104     n1 = IFNBLNK(fbname)
105     n2 = ILNBLNK(fbname)
106     ntot = n2 - n1 + 1
107     fname(1:ntot) = fbname(n1:n2)
108     ntot = ntot + 1
109     fname(ntot:ntot) = '.'
110     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
111 edhill 1.2 nfname = ntot+9
112    
113 edhill 1.11 C Add the path to the file name
114 edhill 1.12 IF (mnc_use_outdir) THEN
115     path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
116     npath = ILNBLNK(mnc_out_path)
117     path_fname(1:npath) = mnc_out_path(1:npath)
118     path_fname((npath+1):(npath+1+nfname)) = fname(1:nfname)
119     fname(1:MNC_MAX_CHAR) = path_fname(1:MNC_MAX_CHAR)
120     nfname = npath + 1 + nfname
121     ENDIF
122 edhill 1.11
123 edhill 1.2 C Append to an existing or create a new file
124 edhill 1.9 CALL MNC_CW_FILE_AORC(fname, indf, myThid)
125 edhill 1.2 fid = mnc_f_info(indf,2)
126    
127 edhill 1.3 C Ensure that all the NetCDF dimensions are defined and create a
128     C local copy of them
129 edhill 1.2 DO i = 1,9
130     dimnc(i) = 1
131     ENDDO
132     DO i = 1,mnc_cw_ndim(igrid)
133 edhill 1.3 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
134     dimnc(i) = -1
135     ELSE
136     dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
137     ENDIF
138 edhill 1.9 CALL MNC_DIM_INIT(fname,
139     & mnc_cw_dn(i,igrid), dimnc(i), myThid)
140 edhill 1.2 ENDDO
141    
142     C Ensure that the "grid" is defined
143 edhill 1.9 CALL MNC_GRID_INIT(fname, mnc_cw_gname(igrid),
144     & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)
145 edhill 1.2
146     C Ensure that the variable is defined
147     #ifdef mnc_rtype_D
148 edhill 1.9 CALL MNC_VAR_INIT_DBL(fname,mnc_cw_gname(igrid),vtype, myThid)
149 edhill 1.2 #endif
150     #ifdef mnc_rtype_R
151 edhill 1.9 CALL MNC_VAR_INIT_REAL(fname,mnc_cw_gname(igrid),vtype, myThid)
152 edhill 1.2 #endif
153 edhill 1.6 #ifdef mnc_rtype_I
154 edhill 1.9 CALL MNC_VAR_INIT_INT(fname,mnc_cw_gname(igrid),vtype, myThid)
155 edhill 1.6 #endif
156 edhill 1.2 DO i = 1,mnc_fv_ids(indf,1)
157     j = 2 + 3*(i - 1)
158     IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
159     idv = mnc_fv_ids(indf,j+1)
160     indvids = mnc_fd_ind(indf, mnc_f_info(indf,
161     & (mnc_fv_ids(indf,j+2) + 1)) )
162     GOTO 10
163     ENDIF
164     ENDDO
165 edhill 1.6 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_W_YY ERROR: ',
166 edhill 1.2 & 'cannot reference variable ''', vtype, ''''
167     CALL print_error(msgbuf, mythid)
168 edhill 1.5 STOP 'ABNORMAL END: package MNC'
169 edhill 1.2 10 CONTINUE
170    
171 edhill 1.3 C Check for bi,bj indicies
172     bidim = mnc_cw_vbij(1,indv)
173     bjdim = mnc_cw_vbij(2,indv)
174 edhill 1.4 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
175 edhill 1.3
176 edhill 1.2 C Set the dimensions for the in-memory array
177     ndim = mnc_cw_ndim(igrid)
178 edhill 1.3 k = mnc_cw_dims(1,igrid)
179     IF (k .GT. 0) THEN
180     p(1) = k
181     ELSE
182     p(1) = 1
183     ENDIF
184 edhill 1.2 DO i = 2,9
185 edhill 1.3 k = mnc_cw_dims(i,igrid)
186     IF (k .LT. 1) THEN
187     k = 1
188     ENDIF
189     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
190     p(i) = nSx * p(i-1)
191     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
192     p(i) = nSy * p(i-1)
193     ELSE
194     p(i) = k * p(i-1)
195     ENDIF
196 edhill 1.2 ENDDO
197    
198 edhill 1.3 C Set starting and ending indicies for the in-memory array and
199     C the unlimited dimension offset for the NetCDF array
200 edhill 1.2 DO i = 1,9
201 edhill 1.3 udo(i) = 0
202     s(i) = 1
203     e(i) = 1
204     IF (i .LE. ndim) THEN
205     s(i) = mnc_cw_is(i,igrid)
206     e(i) = mnc_cw_ie(i,igrid)
207     ENDIF
208     C Check for the unlimited dimension
209     IF ((i .EQ. ndim)
210     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
211     IF (indu .GT. 0) THEN
212     C Use the indu value
213     udo(i) = indu - 1
214     ELSEIF (indu .EQ. -1) THEN
215     C Append one to the current unlimited dim size
216 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
217 edhill 1.3 udo(i) = unlim_sz
218 edhill 1.2 ELSE
219 edhill 1.3 C Use the current unlimited dim size
220 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
221 edhill 1.3 udo(i) = unlim_sz - 1
222 edhill 1.2 ENDIF
223     ENDIF
224     ENDDO
225 edhill 1.3 IF (bidim .GT. 0) THEN
226     s(bidim) = lbi
227     e(bidim) = lbi
228     ENDIF
229     IF (bjdim .GT. 0) THEN
230     s(bjdim) = lbj
231     e(bjdim) = lbj
232     ENDIF
233 edhill 1.4 CEH3 DO i = 1,9
234     CEH3 write(*,*) 'i,p(i),s(i),e(i) = ', i,p(i),s(i),e(i)
235     CEH3 ENDDO
236 edhill 1.3
237     C Add the global attributes
238 edhill 1.9 CALL MNC_CW_SET_GATTR( fname, lbi,lbj, uniq_tnum, myThid)
239 edhill 1.3
240     C Add the per-variable attributes
241     DO i = 1,mnc_cw_vnat(1,indv)
242 edhill 1.9 CALL MNC_VAR_ADD_ATTR_STR( fname, vtype,
243     & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv), myThid)
244 edhill 1.3 ENDDO
245     DO i = 1,mnc_cw_vnat(2,indv)
246 edhill 1.9 CALL MNC_VAR_ADD_ATTR_INT( fname, vtype,
247     & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv), myThid)
248 edhill 1.3 ENDDO
249     DO i = 1,mnc_cw_vnat(3,indv)
250 edhill 1.9 CALL MNC_VAR_ADD_ATTR_DBL( fname, vtype,
251     & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv), myThid)
252 edhill 1.3 ENDDO
253 edhill 1.2
254 edhill 1.9 CALL MNC_FILE_ENDDEF(fname, myThid)
255 edhill 1.2
256 edhill 1.8 write(msgbuf,'(5a)') 'writing variable type ''',
257     & vtype(nvf:nvl), ''' within file ''',
258     & fname(1:nfname), ''''
259    
260 edhill 1.2 C Write the variable one vector at a time
261 edhill 1.3 DO j7 = s(7),e(7)
262 edhill 1.4 k7 = (j7 - 1)*p(6)
263 edhill 1.3 vstart(7) = udo(7) + j7 - s(7) + 1
264     vcount(7) = 1
265     DO j6 = s(6),e(6)
266 edhill 1.4 k6 = (j6 - 1)*p(5) + k7
267 edhill 1.3 vstart(6) = udo(6) + j6 - s(6) + 1
268     vcount(6) = 1
269     DO j5 = s(5),e(5)
270 edhill 1.4 k5 = (j5 - 1)*p(4) + k6
271 edhill 1.3 vstart(5) = udo(5) + j5 - s(5) + 1
272     vcount(5) = 1
273     DO j4 = s(4),e(4)
274 edhill 1.4 k4 = (j4 - 1)*p(3) + k5
275 edhill 1.3 vstart(4) = udo(4) + j4 - s(4) + 1
276     vcount(4) = 1
277     DO j3 = s(3),e(3)
278 edhill 1.4 k3 = (j3 - 1)*p(2) + k4
279 edhill 1.3 vstart(3) = udo(3) + j3 - s(3) + 1
280     vcount(3) = 1
281     DO j2 = s(2),e(2)
282 edhill 1.4 k2 = (j2 - 1)*p(1) + k3
283 edhill 1.3 vstart(2) = udo(2) + j2 - s(2) + 1
284     vcount(2) = 1
285 edhill 1.1
286 edhill 1.3 kr = 0
287     DO j1 = s(1),e(1)
288     k1 = k2 + j1
289     kr = kr + 1
290     resh(kr) = var(k1)
291     ENDDO
292    
293     vstart(1) = udo(1) + 1
294     vcount(1) = e(1) - s(1) + 1
295 edhill 1.2
296     #ifdef mnc_rtype_D
297     err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
298     #endif
299     #ifdef mnc_rtype_R
300     err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh)
301     #endif
302 edhill 1.6 #ifdef mnc_rtype_I
303     err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh)
304     #endif
305 edhill 1.1
306 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
307 edhill 1.8
308 edhill 1.3 ENDDO
309     ENDDO
310 edhill 1.2 ENDDO
311     ENDDO
312     ENDDO
313     ENDDO
314    
315     C Sync the file
316     err = NF_SYNC(fid)
317     write(msgbuf,'(3a)') 'sync for file ''', fname,
318 edhill 1.6 & ''' in S/R MNC_CW_RX_W_YY'
319 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
320 edhill 1.5
321     ENDDO
322     ENDDO
323    
324     _END_MASTER( myThid )
325    
326     RETURN
327     END
328    
329    
330     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
331    
332    
333     SUBROUTINE MNC_CW_RX_R_YY(
334     I fbname, bi,bj,
335     I vtype,
336 edhill 1.9 I var,
337     I myThid )
338 edhill 1.5
339     implicit none
340    
341     #include "netcdf.inc"
342     #include "mnc_common.h"
343     #include "EEPARAMS.h"
344     #include "SIZE.h"
345    
346     #define mnc_rtype_YY
347    
348     C Arguments
349     integer myThid, bi,bj, indu
350     character*(*) fbname, vtype
351 edhill 1.6 __V var(*)
352 edhill 1.5
353     C Functions
354     integer IFNBLNK, ILNBLNK
355    
356     C Local Variables
357 edhill 1.8 integer i,k, nvf,nvl, n1,n2, igrid, ntot
358 edhill 1.6 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv
359 edhill 1.5 integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
360 edhill 1.6 integer ind_fv_ids, ind_vt, ierr, atype, alen
361 edhill 1.10 integer f_sNx,f_sNy
362 edhill 1.6 integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)
363     integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
364 edhill 1.5 character*(MAX_LEN_MBUF) msgbuf
365     character*(MNC_MAX_CHAR) fname
366 edhill 1.10 integer indfg, fg1,fg2
367 edhill 1.5
368     C Temporary storage for the simultaneous type conversion and
369     C re-shaping before passing to NetCDF
370     #ifdef mnc_rtype_D
371 edhill 1.6 REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
372 edhill 1.5 #endif
373     #ifdef mnc_rtype_R
374 edhill 1.6 REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
375     #endif
376     #ifdef mnc_rtype_I
377     INTEGER resh( sNx + 2*OLx + sNy + 2*OLy )
378 edhill 1.5 #endif
379    
380     C Only do I/O if I am the master thread
381     _BEGIN_MASTER( myThid )
382 edhill 1.10
383     C Get the current index for the unlimited dimension from the file
384     C group (or base) name
385     fg1 = IFNBLNK(fbname)
386     fg2 = ILNBLNK(fbname)
387     CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
388     IF (indfg .LT. 1) THEN
389     write(msgbuf,'(3a)')
390     & 'MNC_CW_RX_W_YY ERROR: file group name ''',
391     & fbname(fg1:fg2), ''' is not defined'
392     CALL print_error(msgbuf, mythid)
393     STOP 'ABNORMAL END: S/R MNC_CW_RX_W_YY'
394     ENDIF
395     indu = mnc_cw_fgud(indfg)
396 edhill 1.5
397     C Check that the Variable Type exists
398     nvf = IFNBLNK(vtype)
399     nvl = ILNBLNK(vtype)
400 edhill 1.9 CALL MNC_GET_IND( MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt, myThid)
401 edhill 1.7 IF (ind_vt .LT. 1) THEN
402 edhill 1.5 write(msgbuf,'(3a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
403     & vtype(nvf:nvl), ''' is not defined'
404     CALL print_error(msgbuf, mythid)
405     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
406     ENDIF
407     igrid = mnc_cw_vgind(ind_vt)
408    
409     C Check for bi,bj indicies
410 edhill 1.6 bidim = mnc_cw_vbij(1,ind_vt)
411     bjdim = mnc_cw_vbij(2,ind_vt)
412 edhill 1.5
413     C Set the bi,bj indicies
414     bis = bi
415     bie = bi
416     IF (bi .LT. 1) THEN
417     bis = 1
418     bie = nSx
419     ENDIF
420     bjs = bj
421     bje = bj
422     IF (bj .LT. 1) THEN
423     bjs = 1
424     bje = nSy
425     ENDIF
426    
427     DO lbj = bjs,bje
428     DO lbi = bis,bie
429    
430     C Create the file name
431 edhill 1.9 CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)
432 edhill 1.5 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
433     n1 = IFNBLNK(fbname)
434     n2 = ILNBLNK(fbname)
435     ntot = n2 - n1 + 1
436     fname(1:ntot) = fbname(n1:n2)
437     ntot = ntot + 1
438     fname(ntot:ntot) = '.'
439     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
440     nfname = ntot+9
441    
442     C Open the existing file
443 edhill 1.9 CALL MNC_FILE_TRY_READ( fname, ierr, indf, myThid)
444 edhill 1.5
445     C Check that the variable (VType) is defined within the file
446 edhill 1.9 CALL MNC_GET_FVINDS( fname, vtype, indf, ind_fv_ids, myThid)
447 edhill 1.5 IF ((indf .LT. 1) .OR. (ind_fv_ids .LT. 1)) THEN
448     write(msgbuf,'(4a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
449     & vtype(nvf:nvl), ''' is not defined within file ''',
450     & fname(1:nfname)
451     CALL print_error(msgbuf, mythid)
452     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
453     ENDIF
454     fid = mnc_f_info(indf,2)
455 edhill 1.6 idv = mnc_fv_ids(indf,ind_fv_ids+1)
456    
457     C Check that the current sNy,sNy values and the in-file values
458     C are compatible and WARN (only warn) if not
459     f_sNx = -1
460     f_sNy = -1
461     err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNx',atype,alen)
462     IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
463     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', f_sNx)
464 edhill 1.9 CALL MNC_HANDLE_ERR(err,
465     & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R_YY',
466     & myThid)
467 edhill 1.6 ENDIF
468     err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNy',atype,alen)
469     IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
470     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', f_sNy)
471 edhill 1.9 CALL MNC_HANDLE_ERR(err,
472     & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R_YY',
473     & myThid)
474 edhill 1.6 ENDIF
475 edhill 1.5 IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
476 edhill 1.6 write(msgbuf,'(5a)') 'MNC_CW_RX_R_YY WARNING: the ',
477     & 'attributes ''sNx'' and ''sNy'' within the file ''',
478     & fname(1:nfname), ''' do not exist or do not match ',
479     & 'the current sizes within the model'
480 edhill 1.5 CALL print_error(msgbuf, mythid)
481     ENDIF
482    
483 edhill 1.6 C Check that the in-memory variable and the in-file variables
484     C are of compatible sizes
485 edhill 1.8 C ires = 1
486 edhill 1.9 C CALL MNC_CHK_VTYP_R_NCVAR( ind_vt,
487 edhill 1.8 C & indf, ind_fv_ids, indu, ires)
488     C IF (ires .LT. 0) THEN
489     C write(msgbuf,'(7a)') 'MNC_CW_RX_R_YY WARNING: the sizes ',
490     C & 'of the in-program variable ''', vtype(nvf:nvl),
491     C & ''' and the corresponding variable within file ''',
492     C & fname(1:nfname), ''' are not compatible -- please ',
493     C & 'check the sizes'
494     C CALL print_error(msgbuf, mythid)
495     C STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
496     C ENDIF
497 edhill 1.5
498 edhill 1.6 C Check for bi,bj indicies
499     bidim = mnc_cw_vbij(1,ind_vt)
500     bjdim = mnc_cw_vbij(2,ind_vt)
501    
502     C Set the dimensions for the in-memory array
503     ndim = mnc_cw_ndim(igrid)
504     k = mnc_cw_dims(1,igrid)
505     IF (k .GT. 0) THEN
506     p(1) = k
507     ELSE
508     p(1) = 1
509     ENDIF
510     DO i = 2,9
511     k = mnc_cw_dims(i,igrid)
512     IF (k .LT. 1) THEN
513     k = 1
514     ENDIF
515     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
516     p(i) = nSx * p(i-1)
517     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
518     p(i) = nSy * p(i-1)
519     ELSE
520     p(i) = k * p(i-1)
521     ENDIF
522     ENDDO
523    
524     C Set starting and ending indicies for the in-memory array and
525     C the unlimited dimension offset for the NetCDF array
526     DO i = 1,9
527     udo(i) = 0
528     s(i) = 1
529     e(i) = 1
530     IF (i .LE. ndim) THEN
531     s(i) = mnc_cw_is(i,igrid)
532     e(i) = mnc_cw_ie(i,igrid)
533     ENDIF
534     C Check for the unlimited dimension
535     IF ((i .EQ. ndim)
536     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
537     IF (indu .GT. 0) THEN
538     C Use the indu value
539     udo(i) = indu - 1
540     ELSEIF (indu .EQ. -1) THEN
541     C Append one to the current unlimited dim size
542 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
543 edhill 1.6 udo(i) = unlim_sz
544     ELSE
545     C Use the current unlimited dim size
546 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
547 edhill 1.6 udo(i) = unlim_sz - 1
548     ENDIF
549     ENDIF
550     ENDDO
551     IF (bidim .GT. 0) THEN
552     s(bidim) = lbi
553     e(bidim) = lbi
554     ENDIF
555     IF (bjdim .GT. 0) THEN
556     s(bjdim) = lbj
557     e(bjdim) = lbj
558     ENDIF
559    
560 edhill 1.8 C DO i = 9,1,-1
561     C write(*,*) 'i,p(i),s(i),e(i) = ', i,': ',p(i),s(i),e(i)
562     C ENDDO
563 edhill 1.6
564 edhill 1.9 CALL MNC_FILE_ENDDEF(fname, myThid)
565 edhill 1.6
566     write(msgbuf,'(5a)') 'reading variable type ''',
567     & vtype(nvf:nvl), ''' within file ''',
568     & fname(1:nfname), ''''
569    
570     C Read the variable one vector at a time
571     DO j7 = s(7),e(7)
572     k7 = (j7 - 1)*p(6)
573     vstart(7) = udo(7) + j7 - s(7) + 1
574     vcount(7) = 1
575     DO j6 = s(6),e(6)
576     k6 = (j6 - 1)*p(5) + k7
577     vstart(6) = udo(6) + j6 - s(6) + 1
578     vcount(6) = 1
579     DO j5 = s(5),e(5)
580     k5 = (j5 - 1)*p(4) + k6
581     vstart(5) = udo(5) + j5 - s(5) + 1
582     vcount(5) = 1
583     DO j4 = s(4),e(4)
584     k4 = (j4 - 1)*p(3) + k5
585     vstart(4) = udo(4) + j4 - s(4) + 1
586     vcount(4) = 1
587     DO j3 = s(3),e(3)
588     k3 = (j3 - 1)*p(2) + k4
589     vstart(3) = udo(3) + j3 - s(3) + 1
590     vcount(3) = 1
591     DO j2 = s(2),e(2)
592     k2 = (j2 - 1)*p(1) + k3
593     vstart(2) = udo(2) + j2 - s(2) + 1
594     vcount(2) = 1
595    
596     vstart(1) = udo(1) + 1
597     vcount(1) = e(1) - s(1) + 1
598    
599     #ifdef mnc_rtype_D
600     err = NF_GET_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
601     #endif
602     #ifdef mnc_rtype_R
603     err = NF_GET_VARA_REAL(fid, idv, vstart, vcount, resh)
604     #endif
605     #ifdef mnc_rtype_I
606     err = NF_GET_VARA_INT(fid, idv, vstart, vcount, resh)
607     #endif
608    
609 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
610 edhill 1.6
611     kr = 0
612     DO j1 = s(1),e(1)
613     k1 = k2 + j1
614     kr = kr + 1
615     var(k1) = resh(kr)
616     ENDDO
617    
618    
619     ENDDO
620     ENDDO
621     ENDDO
622     ENDDO
623     ENDDO
624     ENDDO
625 edhill 1.8
626     C Close the file
627 edhill 1.9 CALL MNC_FILE_CLOSE(fname, myThid)
628 edhill 1.1
629 edhill 1.6 C End the lbj,lbi loops
630 edhill 1.1 ENDDO
631     ENDDO
632    
633     _END_MASTER( myThid )
634    
635     RETURN
636     END
637    
638     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
639    
640     CEH3 ;;; Local Variables: ***
641     CEH3 ;;; mode:fortran ***
642     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22