/[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.5 - (hide annotations) (download)
Thu Feb 26 22:31:58 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.4: +155 -6 lines
 o fix the calling sequence for MNC
 o add coordinates to the variables within the "state" file
 o reads still unfinished

1 edhill 1.5 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.4 2004/02/05 05:42:07 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 myThid,
10     I fbname, bi,bj,
11     I vtype,
12     I indu,
13     I var )
14    
15     implicit none
16    
17     #include "netcdf.inc"
18     #include "mnc_common.h"
19     #include "EEPARAMS.h"
20 edhill 1.2 #include "SIZE.h"
21    
22     #define mnc_rtype_YY
23 edhill 1.1
24     C Arguments
25     integer myThid, bi,bj, indu
26     character*(*) fbname, vtype
27     _RX var(*)
28    
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.1 character*(MAX_LEN_MBUF) msgbuf
39     character*(MNC_MAX_CHAR) fname
40    
41     C Temporary storage for the simultaneous type conversion and
42     C re-shaping before passing to NetCDF
43     #ifdef mnc_rtype_D
44     REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
45     #endif
46     #ifdef mnc_rtype_R
47     REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
48     #endif
49    
50     C Only do I/O if I am the master thread
51     _BEGIN_MASTER( myThid )
52    
53     C Check that the Variable Type exists
54     nvf = IFNBLNK(vtype)
55     nvl = ILNBLNK(vtype)
56     CALL MNC_GET_IND(myThid, MNC_MAX_ID, vtype, mnc_cw_vname, indv)
57 edhill 1.2 IF (indv .LT. 1) THEN
58 edhill 1.1 write(msgbuf,'(3a)') 'MNC_CW_RX_WRITES_YY ERROR: vtype ''',
59 edhill 1.2 & vtype(nvf:nvl), ''' is not defined'
60 edhill 1.1 CALL print_error(msgbuf, mythid)
61 edhill 1.5 STOP 'ABNORMAL END: S/R MNC_CW_RX_WRITES_YY'
62 edhill 1.1 ENDIF
63 edhill 1.2 igrid = mnc_cw_vgind(indv)
64 edhill 1.1
65 edhill 1.5 C Set the bi,bj indicies
66 edhill 1.2 bis = bi
67     bie = bi
68 edhill 1.1 IF (bi .LT. 1) THEN
69     bis = 1
70     bie = nSx
71     ENDIF
72 edhill 1.2 bjs = bj
73     bje = bj
74 edhill 1.1 IF (bj .LT. 1) THEN
75     bjs = 1
76     bje = nSy
77     ENDIF
78    
79 edhill 1.2 DO lbj = bjs,bje
80     DO lbi = bis,bie
81 edhill 1.1
82     C Create the file name
83 edhill 1.2 CALL MNC_CW_GET_TILE_NUM(myThid, lbi,lbj, uniq_tnum)
84 edhill 1.1 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
85     n1 = IFNBLNK(fbname)
86     n2 = ILNBLNK(fbname)
87     ntot = n2 - n1 + 1
88     fname(1:ntot) = fbname(n1:n2)
89     ntot = ntot + 1
90     fname(ntot:ntot) = '.'
91     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
92 edhill 1.2 nfname = ntot+9
93    
94     C Append to an existing or create a new file
95     CALL MNC_CW_FILE_AORC(myThid, fname, indf)
96     fid = mnc_f_info(indf,2)
97    
98 edhill 1.3 C Ensure that all the NetCDF dimensions are defined and create a
99     C local copy of them
100 edhill 1.2 DO i = 1,9
101     dimnc(i) = 1
102     ENDDO
103     DO i = 1,mnc_cw_ndim(igrid)
104 edhill 1.3 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
105     dimnc(i) = -1
106     ELSE
107     dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
108     ENDIF
109 edhill 1.2 CALL MNC_DIM_INIT(myThid,fname,
110     & mnc_cw_dn(i,igrid), dimnc(i) )
111     ENDDO
112    
113     C Ensure that the "grid" is defined
114     CALL MNC_GRID_INIT(myThid,fname, mnc_cw_gname(igrid),
115     & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid))
116    
117     C Ensure that the variable is defined
118     #ifdef mnc_rtype_D
119     CALL MNC_VAR_INIT_DBL(myThid,fname,mnc_cw_gname(igrid),vtype)
120     #endif
121     #ifdef mnc_rtype_R
122     CALL MNC_VAR_INIT_REAL(myThid,fname,mnc_cw_gname(igrid),vtype)
123     #endif
124     DO i = 1,mnc_fv_ids(indf,1)
125     j = 2 + 3*(i - 1)
126     IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
127     idv = mnc_fv_ids(indf,j+1)
128     indvids = mnc_fd_ind(indf, mnc_f_info(indf,
129     & (mnc_fv_ids(indf,j+2) + 1)) )
130     GOTO 10
131     ENDIF
132     ENDDO
133     write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_WRITES_YY ERROR: ',
134     & 'cannot reference variable ''', vtype, ''''
135     CALL print_error(msgbuf, mythid)
136 edhill 1.5 STOP 'ABNORMAL END: package MNC'
137 edhill 1.2 10 CONTINUE
138    
139 edhill 1.3 C Check for bi,bj indicies
140     bidim = mnc_cw_vbij(1,indv)
141     bjdim = mnc_cw_vbij(2,indv)
142 edhill 1.4 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
143 edhill 1.3
144 edhill 1.2 C Set the dimensions for the in-memory array
145     ndim = mnc_cw_ndim(igrid)
146 edhill 1.3 k = mnc_cw_dims(1,igrid)
147     IF (k .GT. 0) THEN
148     p(1) = k
149     ELSE
150     p(1) = 1
151     ENDIF
152 edhill 1.2 DO i = 2,9
153 edhill 1.3 k = mnc_cw_dims(i,igrid)
154     IF (k .LT. 1) THEN
155     k = 1
156     ENDIF
157     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
158     p(i) = nSx * p(i-1)
159     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
160     p(i) = nSy * p(i-1)
161     ELSE
162     p(i) = k * p(i-1)
163     ENDIF
164 edhill 1.2 ENDDO
165    
166 edhill 1.3 C Set starting and ending indicies for the in-memory array and
167     C the unlimited dimension offset for the NetCDF array
168 edhill 1.2 DO i = 1,9
169 edhill 1.3 udo(i) = 0
170     s(i) = 1
171     e(i) = 1
172     IF (i .LE. ndim) THEN
173     s(i) = mnc_cw_is(i,igrid)
174     e(i) = mnc_cw_ie(i,igrid)
175     ENDIF
176     C Check for the unlimited dimension
177     IF ((i .EQ. ndim)
178     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
179     IF (indu .GT. 0) THEN
180     C Use the indu value
181     udo(i) = indu - 1
182     ELSEIF (indu .EQ. -1) THEN
183     C Append one to the current unlimited dim size
184     CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
185     udo(i) = unlim_sz
186 edhill 1.2 ELSE
187 edhill 1.3 C Use the current unlimited dim size
188     CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
189     udo(i) = unlim_sz - 1
190 edhill 1.2 ENDIF
191     ENDIF
192     ENDDO
193 edhill 1.3 IF (bidim .GT. 0) THEN
194     s(bidim) = lbi
195     e(bidim) = lbi
196     ENDIF
197     IF (bjdim .GT. 0) THEN
198     s(bjdim) = lbj
199     e(bjdim) = lbj
200     ENDIF
201 edhill 1.4 CEH3 DO i = 1,9
202     CEH3 write(*,*) 'i,p(i),s(i),e(i) = ', i,p(i),s(i),e(i)
203     CEH3 ENDDO
204 edhill 1.3
205     C Add the global attributes
206     CALL MNC_CW_SET_GATTR(myThid, fname, lbi,lbj, uniq_tnum)
207    
208     C Add the per-variable attributes
209     DO i = 1,mnc_cw_vnat(1,indv)
210     CALL MNC_VAR_ADD_ATTR_STR(myThid, fname, vtype,
211     & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv))
212     ENDDO
213     DO i = 1,mnc_cw_vnat(2,indv)
214     CALL MNC_VAR_ADD_ATTR_INT(myThid, fname, vtype,
215     & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv))
216     ENDDO
217     DO i = 1,mnc_cw_vnat(3,indv)
218     CALL MNC_VAR_ADD_ATTR_DBL(myThid, fname, vtype,
219     & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv))
220     ENDDO
221 edhill 1.2
222     CALL MNC_FILE_ENDDEF(myThid,fname)
223    
224     C Write the variable one vector at a time
225 edhill 1.3 DO j7 = s(7),e(7)
226 edhill 1.4 k7 = (j7 - 1)*p(6)
227 edhill 1.3 vstart(7) = udo(7) + j7 - s(7) + 1
228     vcount(7) = 1
229     DO j6 = s(6),e(6)
230 edhill 1.4 k6 = (j6 - 1)*p(5) + k7
231 edhill 1.3 vstart(6) = udo(6) + j6 - s(6) + 1
232     vcount(6) = 1
233     DO j5 = s(5),e(5)
234 edhill 1.4 k5 = (j5 - 1)*p(4) + k6
235 edhill 1.3 vstart(5) = udo(5) + j5 - s(5) + 1
236     vcount(5) = 1
237     DO j4 = s(4),e(4)
238 edhill 1.4 k4 = (j4 - 1)*p(3) + k5
239 edhill 1.3 vstart(4) = udo(4) + j4 - s(4) + 1
240     vcount(4) = 1
241     DO j3 = s(3),e(3)
242 edhill 1.4 k3 = (j3 - 1)*p(2) + k4
243 edhill 1.3 vstart(3) = udo(3) + j3 - s(3) + 1
244     vcount(3) = 1
245     DO j2 = s(2),e(2)
246 edhill 1.4 k2 = (j2 - 1)*p(1) + k3
247 edhill 1.3 vstart(2) = udo(2) + j2 - s(2) + 1
248     vcount(2) = 1
249 edhill 1.1
250 edhill 1.3 kr = 0
251     DO j1 = s(1),e(1)
252     k1 = k2 + j1
253     kr = kr + 1
254     resh(kr) = var(k1)
255     ENDDO
256    
257     vstart(1) = udo(1) + 1
258     vcount(1) = e(1) - s(1) + 1
259 edhill 1.2
260     #ifdef mnc_rtype_D
261     err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
262     #endif
263     #ifdef mnc_rtype_R
264     err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh)
265     #endif
266 edhill 1.1
267 edhill 1.3 ENDDO
268     ENDDO
269 edhill 1.2 ENDDO
270     ENDDO
271     ENDDO
272     ENDDO
273    
274     C Sync the file
275     err = NF_SYNC(fid)
276     write(msgbuf,'(3a)') 'sync for file ''', fname,
277     & ''' in S/R MNC_CW_RX_WRITES_YY'
278     CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
279 edhill 1.5
280     ENDDO
281     ENDDO
282    
283     _END_MASTER( myThid )
284    
285     RETURN
286     END
287    
288    
289     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
290    
291    
292     SUBROUTINE MNC_CW_RX_R_YY(
293     I myThid,
294     I fbname, bi,bj,
295     I vtype,
296     I indu,
297     I var )
298    
299     implicit none
300    
301     #include "netcdf.inc"
302     #include "mnc_common.h"
303     #include "EEPARAMS.h"
304     #include "SIZE.h"
305    
306     #define mnc_rtype_YY
307    
308     C Arguments
309     integer myThid, bi,bj, indu
310     character*(*) fbname, vtype
311     _RX var(*)
312    
313     C Functions
314     integer IFNBLNK, ILNBLNK
315    
316     C Local Variables
317     integer i,j,k, indv,nvf,nvl, n1,n2, igrid, ntot
318     integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv, indvids
319     integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
320     integer ind_fv_ids, ind_vt
321     integer f_sNx,f_sNy,f_OLx,f_OLy, ires
322     character*(MAX_LEN_MBUF) msgbuf
323     character*(MNC_MAX_CHAR) fname
324    
325     C Temporary storage for the simultaneous type conversion and
326     C re-shaping before passing to NetCDF
327     #ifdef mnc_rtype_D
328     REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
329     #endif
330     #ifdef mnc_rtype_R
331     REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
332     #endif
333    
334     C Only do I/O if I am the master thread
335     _BEGIN_MASTER( myThid )
336    
337     C Check that the Variable Type exists
338     nvf = IFNBLNK(vtype)
339     nvl = ILNBLNK(vtype)
340     CALL MNC_GET_IND(myThid, MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt)
341     IF (indv .LT. 1) THEN
342     write(msgbuf,'(3a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
343     & vtype(nvf:nvl), ''' is not defined'
344     CALL print_error(msgbuf, mythid)
345     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
346     ENDIF
347     igrid = mnc_cw_vgind(ind_vt)
348    
349     C Check for bi,bj indicies
350     bidim = mnc_cw_vbij(1,indv)
351     bjdim = mnc_cw_vbij(2,indv)
352    
353     C Set the bi,bj indicies
354     bis = bi
355     bie = bi
356     IF (bi .LT. 1) THEN
357     bis = 1
358     bie = nSx
359     ENDIF
360     bjs = bj
361     bje = bj
362     IF (bj .LT. 1) THEN
363     bjs = 1
364     bje = nSy
365     ENDIF
366    
367     DO lbj = bjs,bje
368     DO lbi = bis,bie
369    
370     C Create the file name
371     CALL MNC_CW_GET_TILE_NUM(myThid, lbi,lbj, uniq_tnum)
372     fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
373     n1 = IFNBLNK(fbname)
374     n2 = ILNBLNK(fbname)
375     ntot = n2 - n1 + 1
376     fname(1:ntot) = fbname(n1:n2)
377     ntot = ntot + 1
378     fname(ntot:ntot) = '.'
379     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
380     nfname = ntot+9
381    
382     C Open the existing file
383     CALL MNC_FILE_OPEN(myThid, fname, 1, indf)
384    
385     C Check that the variable (VType) is defined within the file
386     CALL MNC_GET_FVINDS(myThid, fname, vtype, indf, ind_fv_ids)
387     IF ((indf .LT. 1) .OR. (ind_fv_ids .LT. 1)) THEN
388     write(msgbuf,'(4a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
389     & vtype(nvf:nvl), ''' is not defined within file ''',
390     & fname(1:nfname)
391     CALL print_error(msgbuf, mythid)
392     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
393     ENDIF
394     fid = mnc_f_info(indf,2)
395    
396     C Check that the VType sizes and in-file sizes match
397     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', NF_INT, 1, f_sNx)
398     CALL MNC_HANDLE_ERR(myThid, err,
399     & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R_YY')
400     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', NF_INT, 1, f_sNy)
401     CALL MNC_HANDLE_ERR(myThid, err,
402     & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R_YY')
403     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'OLx', NF_INT, 1, f_OLx)
404     CALL MNC_HANDLE_ERR(myThid, err,
405     & 'reading attribute ''OLx'' in S/R MNC_CW_RX_R_YY')
406     err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'OLy', NF_INT, 1, f_OLy)
407     CALL MNC_HANDLE_ERR(myThid, err,
408     & 'reading attribute ''OLy'' in S/R MNC_CW_RX_R_YY')
409     IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
410     write(msgbuf,'(5a)') 'MNC_CW_RX_R_YY ERROR: the sizes of ',
411     & '''sNx'' and ''sNy'' within the file ''',
412     & fname(1:nfname), ''' do not match the current sizes',
413     & ' within the model'
414     CALL print_error(msgbuf, mythid)
415     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
416     ENDIF
417    
418     CALL MNC_COMP_VTYPE_VAR(myThid,ind_vt, indf,ind_fv_ids, ires)
419    
420     IF (ires .LT. 0) THEN
421     write(msgbuf,'(7a)') 'MNC_CW_RX_R_YY ERROR: the sizes of ',
422     & ' the in-program variable ''', vtype(nvf:nvl),
423     & ''' and the corresponding variable within file ''',
424     & fname(1:nfname), ''' are not compatible -- please ',
425     & 'check the sizes!'
426     CALL print_error(msgbuf, mythid)
427     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
428     ENDIF
429    
430 edhill 1.1
431     ENDDO
432     ENDDO
433    
434     _END_MASTER( myThid )
435    
436     RETURN
437     END
438    
439     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
440    
441     CEH3 ;;; Local Variables: ***
442     CEH3 ;;; mode:fortran ***
443     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22