/[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.19 - (hide annotations) (download)
Thu Oct 7 01:48:08 2004 UTC (19 years, 8 months ago) by edhill
Branch: MAIN
Changes since 1.18: +66 -1 lines
 o fixes for passing scalars to mnc_cw_*

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

  ViewVC Help
Powered by ViewVC 1.1.22