/[MITgcm]/MITgcm/pkg/mnc/mnc_cw_readwrite.template
ViewVC logotype

Contents of /MITgcm/pkg/mnc/mnc_cw_readwrite.template

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.3 - (show annotations) (download)
Thu Feb 5 00:13:47 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.2: +124 -50 lines
 o getting closer to a usable MNC package through the "cw" layer:
   - numerous bug fixes
   - global attributes added
   - improved handling of the unlimited dimension
   - "cw" can handle variables with up to 7 dimensions
   - added list of pre-defined grid types

1 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.2 2004/02/04 05:45:09 edhill Exp $
2 C $Name: $
3
4 #include "MNC_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 SUBROUTINE MNC_CW_RX_W_YY(
9 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 #include "SIZE.h"
21
22 #define mnc_rtype_YY
23
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 integer i,j,k, indv,nvf,nvl, n1,n2, igrid, ntot
34 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv, indvids
35 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 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 IF (indv .LT. 1) THEN
58 write(msgbuf,'(3a)') 'MNC_CW_RX_WRITES_YY ERROR: vtype ''',
59 & vtype(nvf:nvl), ''' is not defined'
60 CALL print_error(msgbuf, mythid)
61 stop 'ABNORMAL END: S/R MNC_CW_RX_WRITES_YY'
62 ENDIF
63 igrid = mnc_cw_vgind(indv)
64
65 C
66 bis = bi
67 bie = bi
68 IF (bi .LT. 1) THEN
69 bis = 1
70 bie = nSx
71 ENDIF
72 bjs = bj
73 bje = bj
74 IF (bj .LT. 1) THEN
75 bjs = 1
76 bje = nSy
77 ENDIF
78
79 DO lbj = bjs,bje
80 DO lbi = bis,bie
81
82 write(*,*) 'lbi,lbj = ',lbi,lbj, ' ', vtype(nvf:nvl)
83
84 C Create the file name
85 CALL MNC_CW_GET_TILE_NUM(myThid, lbi,lbj, uniq_tnum)
86 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
87 n1 = IFNBLNK(fbname)
88 n2 = ILNBLNK(fbname)
89 ntot = n2 - n1 + 1
90 fname(1:ntot) = fbname(n1:n2)
91 ntot = ntot + 1
92 fname(ntot:ntot) = '.'
93 write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
94 nfname = ntot+9
95
96 C Append to an existing or create a new file
97 CALL MNC_CW_FILE_AORC(myThid, fname, indf)
98 fid = mnc_f_info(indf,2)
99
100 C Ensure that all the NetCDF dimensions are defined and create a
101 C local copy of them
102 DO i = 1,9
103 dimnc(i) = 1
104 ENDDO
105 DO i = 1,mnc_cw_ndim(igrid)
106 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
107 dimnc(i) = -1
108 ELSE
109 dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
110 ENDIF
111 CALL MNC_DIM_INIT(myThid,fname,
112 & mnc_cw_dn(i,igrid), dimnc(i) )
113 ENDDO
114
115 C Ensure that the "grid" is defined
116 CALL MNC_GRID_INIT(myThid,fname, mnc_cw_gname(igrid),
117 & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid))
118
119 C Ensure that the variable is defined
120 #ifdef mnc_rtype_D
121 CALL MNC_VAR_INIT_DBL(myThid,fname,mnc_cw_gname(igrid),vtype)
122 #endif
123 #ifdef mnc_rtype_R
124 CALL MNC_VAR_INIT_REAL(myThid,fname,mnc_cw_gname(igrid),vtype)
125 #endif
126 DO i = 1,mnc_fv_ids(indf,1)
127 j = 2 + 3*(i - 1)
128 IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
129 idv = mnc_fv_ids(indf,j+1)
130 indvids = mnc_fd_ind(indf, mnc_f_info(indf,
131 & (mnc_fv_ids(indf,j+2) + 1)) )
132 GOTO 10
133 ENDIF
134 ENDDO
135 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_WRITES_YY ERROR: ',
136 & 'cannot reference variable ''', vtype, ''''
137 CALL print_error(msgbuf, mythid)
138 stop 'ABNORMAL END: package MNC'
139 10 CONTINUE
140
141 C Check for bi,bj indicies
142 bidim = mnc_cw_vbij(1,indv)
143 bjdim = mnc_cw_vbij(2,indv)
144
145 C Set the dimensions for the in-memory array
146 ndim = mnc_cw_ndim(igrid)
147 k = mnc_cw_dims(1,igrid)
148 IF (k .GT. 0) THEN
149 p(1) = k
150 ELSE
151 p(1) = 1
152 ENDIF
153 DO i = 2,9
154 k = mnc_cw_dims(i,igrid)
155 IF (k .LT. 1) THEN
156 k = 1
157 ENDIF
158 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
159 p(i) = nSx * p(i-1)
160 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
161 p(i) = nSy * p(i-1)
162 ELSE
163 p(i) = k * p(i-1)
164 ENDIF
165 ENDDO
166
167 C Set starting and ending indicies for the in-memory array and
168 C the unlimited dimension offset for the NetCDF array
169 DO i = 1,9
170 udo(i) = 0
171 s(i) = 1
172 e(i) = 1
173 IF (i .LE. ndim) THEN
174 s(i) = mnc_cw_is(i,igrid)
175 e(i) = mnc_cw_ie(i,igrid)
176 ENDIF
177 C Check for the unlimited dimension
178 IF ((i .EQ. ndim)
179 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
180 IF (indu .GT. 0) THEN
181 C Use the indu value
182 udo(i) = indu - 1
183 ELSEIF (indu .EQ. -1) THEN
184 C Append one to the current unlimited dim size
185 CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
186 udo(i) = unlim_sz
187 ELSE
188 C Use the current unlimited dim size
189 CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
190 udo(i) = unlim_sz - 1
191 ENDIF
192 ENDIF
193 ENDDO
194 IF (bidim .GT. 0) THEN
195 s(bidim) = lbi
196 e(bidim) = lbi
197 ENDIF
198 IF (bjdim .GT. 0) THEN
199 s(bjdim) = lbj
200 e(bjdim) = lbj
201 ENDIF
202 CEH3 DO i = 1,7
203 CEH3 write(*,*) 'i,s(i),e(i) = ', i,s(i),e(i)
204 CEH3 ENDDO
205
206 C Add the global attributes
207 CALL MNC_CW_SET_GATTR(myThid, fname, lbi,lbj, uniq_tnum)
208
209 C Add the per-variable attributes
210 DO i = 1,mnc_cw_vnat(1,indv)
211 CALL MNC_VAR_ADD_ATTR_STR(myThid, fname, vtype,
212 & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv))
213 ENDDO
214 DO i = 1,mnc_cw_vnat(2,indv)
215 CALL MNC_VAR_ADD_ATTR_INT(myThid, fname, vtype,
216 & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv))
217 ENDDO
218 DO i = 1,mnc_cw_vnat(3,indv)
219 CALL MNC_VAR_ADD_ATTR_DBL(myThid, fname, vtype,
220 & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv))
221 ENDDO
222
223 CALL MNC_FILE_ENDDEF(myThid,fname)
224
225 C Write the variable one vector at a time
226 DO j7 = s(7),e(7)
227 k7 = (j7 - s(7))*p(6)
228 vstart(7) = udo(7) + j7 - s(7) + 1
229 vcount(7) = 1
230 DO j6 = s(6),e(6)
231 k6 = (j6 - s(6))*p(5) + k7
232 vstart(6) = udo(6) + j6 - s(6) + 1
233 vcount(6) = 1
234 DO j5 = s(5),e(5)
235 k5 = (j5 - s(5))*p(4) + k6
236 vstart(5) = udo(5) + j5 - s(5) + 1
237 vcount(5) = 1
238 DO j4 = s(4),e(4)
239 k4 = (j4 - s(4))*p(3) + k5
240 vstart(4) = udo(4) + j4 - s(4) + 1
241 vcount(4) = 1
242 DO j3 = s(3),e(3)
243 k3 = (j3 - s(3))*p(2) + k4
244 vstart(3) = udo(3) + j3 - s(3) + 1
245 vcount(3) = 1
246 DO j2 = s(2),e(2)
247 k2 = (j2 - s(2))*p(1) + k3
248 vstart(2) = udo(2) + j2 - s(2) + 1
249 vcount(2) = 1
250
251 CEH3 write(*,*) 's/e: ', k2+s(1), k2+e(1)
252
253 kr = 0
254 DO j1 = s(1),e(1)
255 k1 = k2 + j1
256 kr = kr + 1
257 resh(kr) = var(k1)
258 ENDDO
259
260 vstart(1) = udo(1) + 1
261 vcount(1) = e(1) - s(1) + 1
262
263 #ifdef mnc_rtype_D
264 err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
265 #endif
266 #ifdef mnc_rtype_R
267 err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh)
268 #endif
269
270 ENDDO
271 ENDDO
272 ENDDO
273 ENDDO
274 ENDDO
275 ENDDO
276
277 C Sync the file
278 err = NF_SYNC(fid)
279 write(msgbuf,'(3a)') 'sync for file ''', fname,
280 & ''' in S/R MNC_CW_RX_WRITES_YY'
281 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
282
283 ENDDO
284 ENDDO
285
286 _END_MASTER( myThid )
287
288 RETURN
289 END
290
291 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
292
293 CEH3 ;;; Local Variables: ***
294 CEH3 ;;; mode:fortran ***
295 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22