/[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.31 - (hide annotations) (download)
Mon Jun 27 20:19:52 2005 UTC (18 years, 11 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57o_post, checkpoint57m_post, checkpoint57k_post, checkpoint57r_post, checkpoint57n_post, checkpoint57p_post, checkpoint57q_post, checkpoint57j_post, checkpoint57l_post
Changes since 1.30: +12 -4 lines
 o add a flag (off by default) that includes nIter0 in the MNC file names

1 edhill 1.31 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.30 2005/06/24 19:43:52 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 edhill 1.20 integer myThid, bi,bj
27 edhill 1.19 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 edhill 1.20 C A scalar version of MNC_CW_RX_W() for compilers that cannot
52     C gracefully handle the conversion on their own.
53    
54     C !USES:
55     implicit none
56    
57     C !INPUT PARAMETERS:
58     integer myThid, bi,bj
59     character*(*) stype, fbname, vtype
60 jmc 1.21 __V var(*)
61 edhill 1.20 INTEGER offsets(9)
62     CEOP
63     INTEGER i
64    
65     DO i = 1,9
66     offsets(i) = 0
67     ENDDO
68 jmc 1.21 CALL MNC_CW_RX_W_OFFSET(stype,fbname,bi,bj,vtype, var,
69 edhill 1.20 & offsets, myThid)
70    
71     RETURN
72     END
73    
74     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
75     CBOP 0
76     C !ROUTINE: MNC_CW_RX_W_OFFSET
77    
78     C !INTERFACE:
79     SUBROUTINE MNC_CW_RX_W_OFFSET(
80     I stype,
81     I fbname, bi,bj,
82     I vtype,
83     I var,
84     I offsets,
85     I myThid )
86    
87     C !DESCRIPTION:
88 edhill 1.15 C This subroutine writes one variable to a file or a file group,
89     C depending upon the tile indicies.
90    
91     C !USES:
92 edhill 1.1 implicit none
93     #include "netcdf.inc"
94     #include "mnc_common.h"
95 edhill 1.12 #include "SIZE.h"
96 edhill 1.24 #include "MNC_SIZE.h"
97 edhill 1.1 #include "EEPARAMS.h"
98 edhill 1.12 #include "PARAMS.h"
99 edhill 1.18 #include "MNC_PARAMS.h"
100 edhill 1.2
101 edhill 1.15 C !INPUT PARAMETERS:
102 edhill 1.20 integer myThid, bi,bj
103 edhill 1.14 character*(*) stype, fbname, vtype
104 edhill 1.6 __V var(*)
105 edhill 1.20 INTEGER offsets(*)
106 edhill 1.17 CEOP
107 edhill 1.1
108 edhill 1.15 C !LOCAL VARIABLES:
109 edhill 1.20 integer i,j,k, indv,nvf,nvl, n1,n2, igrid, ntot, indu
110 edhill 1.22 integer bis,bie, bjs,bje, uniq_tnum, nfname, iseq
111 edhill 1.16 integer fid, idv, indvids, ndim, indf, err
112 edhill 1.15 integer lbi,lbj, bidim,bjdim, unlim_sz, kr
113     integer p(9),s(9),e(9), dimnc(9)
114     integer vstart(9),vcount(9), udo(9)
115 edhill 1.3 integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
116 edhill 1.11 integer indfg, fg1,fg2, npath
117 edhill 1.1 character*(MAX_LEN_MBUF) msgbuf
118     character*(MNC_MAX_CHAR) fname
119 edhill 1.11 character*(MNC_MAX_CHAR) path_fname
120 edhill 1.24 REAL*8 resh_d( MNC_MAX_BUFF )
121     REAL*4 resh_r( MNC_MAX_BUFF )
122     INTEGER resh_i( MNC_MAX_BUFF )
123 edhill 1.23 #ifdef HAVE_STAT
124     integer ntotenc, ncenc, nbytes, fs_isdone
125     character*(200) cenc
126     integer ienc(200)
127     REAL*8 fsnu
128     #endif
129 edhill 1.17
130 edhill 1.15 C Functions
131     integer IFNBLNK, ILNBLNK
132 edhill 1.1
133     C Only do I/O if I am the master thread
134     _BEGIN_MASTER( myThid )
135    
136 edhill 1.10 C Get the current index for the unlimited dimension from the file
137     C group (or base) name
138     fg1 = IFNBLNK(fbname)
139     fg2 = ILNBLNK(fbname)
140     CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
141     IF (indfg .LT. 1) THEN
142     write(msgbuf,'(3a)')
143 edhill 1.14 & 'MNC_CW_RX_W ERROR: file group name ''',
144 edhill 1.10 & fbname(fg1:fg2), ''' is not defined'
145     CALL print_error(msgbuf, mythid)
146 edhill 1.14 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
147 edhill 1.10 ENDIF
148     indu = mnc_cw_fgud(indfg)
149 edhill 1.22 iseq = mnc_cw_fgis(indfg)
150 edhill 1.23 C write(*,*) 'indu,iseq = ', indu, iseq
151 edhill 1.10
152 edhill 1.1 C Check that the Variable Type exists
153     nvf = IFNBLNK(vtype)
154     nvl = ILNBLNK(vtype)
155 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, vtype, mnc_cw_vname, indv, myThid)
156 edhill 1.2 IF (indv .LT. 1) THEN
157 edhill 1.14 write(msgbuf,'(3a)') 'MNC_CW_RX_W ERROR: vtype ''',
158 edhill 1.2 & vtype(nvf:nvl), ''' is not defined'
159 edhill 1.1 CALL print_error(msgbuf, mythid)
160 edhill 1.14 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
161 edhill 1.1 ENDIF
162 edhill 1.2 igrid = mnc_cw_vgind(indv)
163 edhill 1.1
164 edhill 1.5 C Set the bi,bj indicies
165 edhill 1.2 bis = bi
166     bie = bi
167 edhill 1.1 IF (bi .LT. 1) THEN
168     bis = 1
169     bie = nSx
170     ENDIF
171 edhill 1.2 bjs = bj
172     bje = bj
173 edhill 1.1 IF (bj .LT. 1) THEN
174     bjs = 1
175     bje = nSy
176     ENDIF
177    
178 edhill 1.2 DO lbj = bjs,bje
179     DO lbi = bis,bie
180 edhill 1.1
181 edhill 1.23 #ifdef HAVE_STAT
182     fs_isdone = 0
183     #endif
184     10 CONTINUE
185    
186 edhill 1.1 C Create the file name
187 edhill 1.9 CALL MNC_CW_GET_TILE_NUM(lbi,lbj, uniq_tnum, myThid)
188 edhill 1.1 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
189     n1 = IFNBLNK(fbname)
190     n2 = ILNBLNK(fbname)
191     ntot = n2 - n1 + 1
192     fname(1:ntot) = fbname(n1:n2)
193     ntot = ntot + 1
194     fname(ntot:ntot) = '.'
195 edhill 1.31 IF ( mnc_use_name_ni0 ) THEN
196     write(fname((ntot+1):(ntot+17)),'(i10.10,a1,i6.6)')
197     & nIter0,'.',uniq_tnum
198     write(fname((ntot+18):(ntot+25)),'(a1,i4.4,a3)')
199     & '.', iseq, '.nc'
200     nfname = ntot + 25
201     ELSE
202     write(fname((ntot+1):(ntot+14)),'(i4.4,a1,i6.6,a3)')
203     & iseq,'.',uniq_tnum, '.nc'
204     nfname = ntot + 14
205     ENDIF
206 edhill 1.2
207 edhill 1.11 C Add the path to the file name
208 edhill 1.12 IF (mnc_use_outdir) THEN
209     path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
210     npath = ILNBLNK(mnc_out_path)
211     path_fname(1:npath) = mnc_out_path(1:npath)
212 edhill 1.13 path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
213 edhill 1.12 fname(1:MNC_MAX_CHAR) = path_fname(1:MNC_MAX_CHAR)
214 edhill 1.13 nfname = npath + nfname
215 edhill 1.12 ENDIF
216 edhill 1.11
217 edhill 1.2 C Append to an existing or create a new file
218 edhill 1.26 CALL MNC_CW_FILE_AORC(fname,indf, lbi,lbj,uniq_tnum, myThid)
219 edhill 1.2 fid = mnc_f_info(indf,2)
220    
221 edhill 1.23 #ifdef HAVE_STAT
222     IF ((mnc_cw_fgig(indfg) .EQ. 1)
223     & .AND. (fs_isdone .EQ. 0)) THEN
224 edhill 1.26 C Decide whether to append to the existing or create a new
225     C file based on the byte count per unlimited dimension
226 edhill 1.23 ncenc = 70
227     cenc(1:26) = 'abcdefghijklmnopqrstuvwxyz'
228     cenc(27:52) = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
229     cenc(53:70) = '0123456789_.,+-=/~'
230     k = nfname
231     IF (k .GT. 200) k = 200
232     ntotenc = 0
233     DO i = 1,k
234     DO j = 1,ncenc
235     IF (fname(i:i) .EQ. cenc(j:j)) THEN
236     ntotenc = ntotenc + 1
237     ienc(ntotenc) = j
238     GOTO 20
239     ENDIF
240     ENDDO
241     20 CONTINUE
242     ENDDO
243     CALL mncfsize(ntotenc, ienc, nbytes)
244     IF (nbytes .GT. 0) THEN
245     CALL MNC_DIM_UNLIM_SIZE(fname, unlim_sz, myThid)
246     fsnu = (1.0 _d 0 + 1.0 _d 0 / DBLE(unlim_sz))
247     & * DBLE(nbytes)
248     IF (fsnu .GT. mnc_max_fsize) THEN
249 edhill 1.25 C Delete the now-full fname from the lookup tables since
250     C we are all done writing to it.
251     CALL MNC_FILE_CLOSE(fname, myThid)
252 edhill 1.23 iseq = iseq + 1
253     indu = 1
254     mnc_cw_fgud(indfg) = 1
255     mnc_cw_fgis(indfg) = iseq
256     fs_isdone = 1
257     GOTO 10
258     ENDIF
259     ENDIF
260     ENDIF
261     #endif /* HAVE_STAT */
262    
263 edhill 1.3 C Ensure that all the NetCDF dimensions are defined and create a
264     C local copy of them
265 edhill 1.2 DO i = 1,9
266     dimnc(i) = 1
267     ENDDO
268     DO i = 1,mnc_cw_ndim(igrid)
269 edhill 1.3 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
270     dimnc(i) = -1
271     ELSE
272     dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
273     ENDIF
274 edhill 1.26
275     C Add the coordinate variables
276 edhill 1.27 CALL MNC_DIM_INIT_ALL_CV(fname,
277     & mnc_cw_dn(i,igrid), dimnc(i), 'Y', lbi,lbj, myThid)
278 edhill 1.26
279 edhill 1.2 ENDDO
280    
281     C Ensure that the "grid" is defined
282 edhill 1.9 CALL MNC_GRID_INIT(fname, mnc_cw_gname(igrid),
283     & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)
284 edhill 1.2
285     C Ensure that the variable is defined
286 edhill 1.14 IF (stype(1:1) .EQ. 'D')
287     & CALL MNC_VAR_INIT_DBL(
288     & fname, mnc_cw_gname(igrid), vtype, myThid)
289     IF (stype(1:1) .EQ. 'R')
290     & CALL MNC_VAR_INIT_REAL(
291     & fname, mnc_cw_gname(igrid), vtype, myThid)
292     IF (stype(1:1) .EQ. 'I')
293     & CALL MNC_VAR_INIT_INT(
294     & fname, mnc_cw_gname(igrid), vtype, myThid)
295    
296 edhill 1.2 DO i = 1,mnc_fv_ids(indf,1)
297     j = 2 + 3*(i - 1)
298     IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
299     idv = mnc_fv_ids(indf,j+1)
300     indvids = mnc_fd_ind(indf, mnc_f_info(indf,
301     & (mnc_fv_ids(indf,j+2) + 1)) )
302 edhill 1.23 GOTO 30
303 edhill 1.2 ENDIF
304     ENDDO
305 edhill 1.14 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_W ERROR: ',
306 edhill 1.2 & 'cannot reference variable ''', vtype, ''''
307     CALL print_error(msgbuf, mythid)
308 edhill 1.5 STOP 'ABNORMAL END: package MNC'
309 edhill 1.23 30 CONTINUE
310 edhill 1.2
311 edhill 1.3 C Check for bi,bj indicies
312     bidim = mnc_cw_vbij(1,indv)
313     bjdim = mnc_cw_vbij(2,indv)
314 edhill 1.4 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
315 edhill 1.3
316 edhill 1.2 C Set the dimensions for the in-memory array
317     ndim = mnc_cw_ndim(igrid)
318 edhill 1.3 k = mnc_cw_dims(1,igrid)
319     IF (k .GT. 0) THEN
320     p(1) = k
321     ELSE
322     p(1) = 1
323     ENDIF
324 edhill 1.2 DO i = 2,9
325 edhill 1.3 k = mnc_cw_dims(i,igrid)
326     IF (k .LT. 1) THEN
327     k = 1
328     ENDIF
329     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
330     p(i) = nSx * p(i-1)
331     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
332     p(i) = nSy * p(i-1)
333     ELSE
334     p(i) = k * p(i-1)
335     ENDIF
336 edhill 1.20 IF (offsets(i) .GT. 0) THEN
337     k = 1
338     p(i) = k * p(i-1)
339     ENDIF
340 edhill 1.2 ENDDO
341    
342 edhill 1.3 C Set starting and ending indicies for the in-memory array and
343     C the unlimited dimension offset for the NetCDF array
344 edhill 1.2 DO i = 1,9
345 edhill 1.3 udo(i) = 0
346     s(i) = 1
347     e(i) = 1
348     IF (i .LE. ndim) THEN
349     s(i) = mnc_cw_is(i,igrid)
350     e(i) = mnc_cw_ie(i,igrid)
351     ENDIF
352     C Check for the unlimited dimension
353     IF ((i .EQ. ndim)
354     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
355     IF (indu .GT. 0) THEN
356     C Use the indu value
357     udo(i) = indu - 1
358     ELSEIF (indu .EQ. -1) THEN
359     C Append one to the current unlimited dim size
360 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
361 edhill 1.3 udo(i) = unlim_sz
362 edhill 1.2 ELSE
363 edhill 1.3 C Use the current unlimited dim size
364 edhill 1.9 CALL MNC_DIM_UNLIM_SIZE( fname, unlim_sz, myThid)
365 edhill 1.3 udo(i) = unlim_sz - 1
366 edhill 1.2 ENDIF
367     ENDIF
368     ENDDO
369 edhill 1.3 IF (bidim .GT. 0) THEN
370     s(bidim) = lbi
371     e(bidim) = lbi
372     ENDIF
373     IF (bjdim .GT. 0) THEN
374     s(bjdim) = lbj
375     e(bjdim) = lbj
376     ENDIF
377 edhill 1.20
378     C Check the offsets
379     DO i = 1,9
380     IF (offsets(i) .GT. 0) THEN
381     udo(i) = udo(i) + offsets(i) - 1
382     s(i) = 1
383     e(i) = 1
384     ENDIF
385     ENDDO
386 edhill 1.3
387     C Add the per-variable attributes
388     DO i = 1,mnc_cw_vnat(1,indv)
389 edhill 1.9 CALL MNC_VAR_ADD_ATTR_STR( fname, vtype,
390     & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv), myThid)
391 edhill 1.3 ENDDO
392     DO i = 1,mnc_cw_vnat(2,indv)
393 edhill 1.9 CALL MNC_VAR_ADD_ATTR_INT( fname, vtype,
394     & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv), myThid)
395 edhill 1.3 ENDDO
396     DO i = 1,mnc_cw_vnat(3,indv)
397 edhill 1.9 CALL MNC_VAR_ADD_ATTR_DBL( fname, vtype,
398     & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv), myThid)
399 edhill 1.3 ENDDO
400 edhill 1.2
401 edhill 1.9 CALL MNC_FILE_ENDDEF(fname, myThid)
402 edhill 1.2
403 edhill 1.8 write(msgbuf,'(5a)') 'writing variable type ''',
404     & vtype(nvf:nvl), ''' within file ''',
405     & fname(1:nfname), ''''
406    
407 edhill 1.20 C DO i = 1,9
408     C write(*,*) 'i,p(i),s(i),e(i),udo(i),offsets(i) = ',
409     C & i,p(i),s(i),e(i),udo(i),offsets(i)
410     C ENDDO
411    
412 edhill 1.2 C Write the variable one vector at a time
413 edhill 1.3 DO j7 = s(7),e(7)
414 edhill 1.4 k7 = (j7 - 1)*p(6)
415 edhill 1.3 vstart(7) = udo(7) + j7 - s(7) + 1
416     vcount(7) = 1
417     DO j6 = s(6),e(6)
418 edhill 1.4 k6 = (j6 - 1)*p(5) + k7
419 edhill 1.3 vstart(6) = udo(6) + j6 - s(6) + 1
420     vcount(6) = 1
421     DO j5 = s(5),e(5)
422 edhill 1.4 k5 = (j5 - 1)*p(4) + k6
423 edhill 1.3 vstart(5) = udo(5) + j5 - s(5) + 1
424     vcount(5) = 1
425     DO j4 = s(4),e(4)
426 edhill 1.4 k4 = (j4 - 1)*p(3) + k5
427 edhill 1.3 vstart(4) = udo(4) + j4 - s(4) + 1
428     vcount(4) = 1
429     DO j3 = s(3),e(3)
430 edhill 1.4 k3 = (j3 - 1)*p(2) + k4
431 edhill 1.3 vstart(3) = udo(3) + j3 - s(3) + 1
432     vcount(3) = 1
433     DO j2 = s(2),e(2)
434 edhill 1.4 k2 = (j2 - 1)*p(1) + k3
435 edhill 1.3 vstart(2) = udo(2) + j2 - s(2) + 1
436     vcount(2) = 1
437 edhill 1.1
438 edhill 1.3 kr = 0
439     vstart(1) = udo(1) + 1
440     vcount(1) = e(1) - s(1) + 1
441 edhill 1.2
442 edhill 1.24 IF (vcount(1) .GT. MNC_MAX_BUFF) THEN
443     write(msgbuf,'(2a,I7,a)') 'MNC_MAX_BUFF is too small',
444     & '--please increase to at least ',
445     & vcount(1), ' in ''MNC_SIZE.h'''
446     CALL PRINT_ERROR(msgBuf , 1)
447     STOP 'ABNORMAL END: S/R MNC_CW_RX_W_OFFSET'
448     ENDIF
449    
450 edhill 1.14 IF (stype(1:1) .EQ. 'D') THEN
451     DO j1 = s(1),e(1)
452     k1 = k2 + j1
453     kr = kr + 1
454     resh_d(kr) = var(k1)
455     ENDDO
456     err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
457     ENDIF
458     IF (stype(1:1) .EQ. 'R') THEN
459     DO j1 = s(1),e(1)
460     k1 = k2 + j1
461     kr = kr + 1
462     resh_r(kr) = var(k1)
463     ENDDO
464     err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh_r)
465     ENDIF
466     IF (stype(1:1) .EQ. 'I') THEN
467     DO j1 = s(1),e(1)
468     k1 = k2 + j1
469     kr = kr + 1
470 edhill 1.29 resh_i(kr) = MNC2I( var(k1) )
471 edhill 1.14 ENDDO
472     err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh_i)
473     ENDIF
474 edhill 1.1
475 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
476 edhill 1.8
477 edhill 1.3 ENDDO
478     ENDDO
479 edhill 1.2 ENDDO
480     ENDDO
481     ENDDO
482     ENDDO
483    
484     C Sync the file
485     err = NF_SYNC(fid)
486     write(msgbuf,'(3a)') 'sync for file ''', fname,
487 edhill 1.14 & ''' in S/R MNC_CW_RX_W'
488 edhill 1.9 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
489 edhill 1.5
490     ENDDO
491     ENDDO
492    
493     _END_MASTER( myThid )
494    
495     RETURN
496     END
497    
498    
499     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
500 edhill 1.17 CBOP 0
501 edhill 1.19 C !ROUTINE: MNC_CW_RX_R_S
502    
503     C !INTERFACE:
504     SUBROUTINE MNC_CW_RX_R_S(
505     I stype,
506     I fbname, bi,bj,
507     I vtype,
508     I var,
509     I myThid )
510    
511     C !DESCRIPTION:
512     C A scalar version of MNC_CW_RX_R() for compilers that cannot
513     C gracefully handle the conversion on their own.
514    
515     C !USES:
516     implicit none
517    
518     C !INPUT PARAMETERS:
519 edhill 1.20 integer myThid, bi,bj
520 edhill 1.19 character*(*) stype, fbname, vtype
521     __V var
522     __V var_arr(1)
523     CEOP
524     var_arr(1) = var
525    
526     CALL MNC_CW_RX_R(stype,fbname,bi,bj,vtype, var_arr, myThid)
527    
528     RETURN
529     END
530    
531    
532     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
533     CBOP 0
534 edhill 1.15 C !ROUTINE: MNC_CW_RX_R
535 edhill 1.5
536 edhill 1.15 C !INTERFACE:
537 edhill 1.14 SUBROUTINE MNC_CW_RX_R(
538     I stype,
539 edhill 1.5 I fbname, bi,bj,
540     I vtype,
541 edhill 1.9 I var,
542     I myThid )
543 edhill 1.5
544 edhill 1.15 C !DESCRIPTION:
545     C This subroutine reads one variable from a file or a file group,
546     C depending upon the tile indicies.
547    
548     C !USES:
549 edhill 1.17 implicit none
550 edhill 1.5 #include "netcdf.inc"
551     #include "mnc_common.h"
552 edhill 1.13 #include "SIZE.h"
553 edhill 1.24 #include "MNC_SIZE.h"
554 edhill 1.5 #include "EEPARAMS.h"
555 edhill 1.13 #include "PARAMS.h"
556 edhill 1.18 #include "MNC_PARAMS.h"
557 edhill 1.5
558 edhill 1.15 C !INPUT PARAMETERS:
559 edhill 1.20 integer myThid, bi,bj
560 edhill 1.14 character*(*) stype, fbname, vtype
561 edhill 1.6 __V var(*)
562 edhill 1.17 CEOP
563 edhill 1.5
564 edhill 1.15 C !LOCAL VARIABLES:
565 edhill 1.20 integer i,k, nvf,nvl, n1,n2, igrid, ntot, indu
566 edhill 1.6 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv
567 edhill 1.28 integer ndim, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
568     integer ind_vt, npath, unlid
569     C integer f_sNx,f_sNy, alen, atype, ind_fv_ids, ierr, indf
570 edhill 1.6 integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)
571     integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
572 edhill 1.5 character*(MAX_LEN_MBUF) msgbuf
573     character*(MNC_MAX_CHAR) fname
574 edhill 1.30 character*(MNC_MAX_CHAR) fname_zs
575 edhill 1.13 character*(MNC_MAX_CHAR) path_fname
576 edhill 1.10 integer indfg, fg1,fg2
577 edhill 1.24 REAL*8 resh_d( MNC_MAX_BUFF )
578     REAL*4 resh_r( MNC_MAX_BUFF )
579     INTEGER resh_i( MNC_MAX_BUFF )
580 edhill 1.17
581 edhill 1.15 C Functions
582     integer IFNBLNK, ILNBLNK
583 edhill 1.5
584     C Only do I/O if I am the master thread
585     _BEGIN_MASTER( myThid )
586 edhill 1.10
587     C Get the current index for the unlimited dimension from the file
588     C group (or base) name
589     fg1 = IFNBLNK(fbname)
590     fg2 = ILNBLNK(fbname)
591     CALL MNC_GET_IND(MNC_MAX_ID, fbname, mnc_cw_fgnm, indfg, myThid)
592     IF (indfg .LT. 1) THEN
593     write(msgbuf,'(3a)')
594 edhill 1.14 & 'MNC_CW_RX_W ERROR: file group name ''',
595 edhill 1.10 & fbname(fg1:fg2), ''' is not defined'
596     CALL print_error(msgbuf, mythid)
597 edhill 1.14 STOP 'ABNORMAL END: S/R MNC_CW_RX_W'
598 edhill 1.10 ENDIF
599     indu = mnc_cw_fgud(indfg)
600 edhill 1.5
601     C Check that the Variable Type exists
602     nvf = IFNBLNK(vtype)
603     nvl = ILNBLNK(vtype)
604 edhill 1.9 CALL MNC_GET_IND( MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt, myThid)
605 edhill 1.7 IF (ind_vt .LT. 1) THEN
606 edhill 1.14 write(msgbuf,'(3a)') 'MNC_CW_RX_R ERROR: vtype ''',
607 edhill 1.5 & vtype(nvf:nvl), ''' is not defined'
608     CALL print_error(msgbuf, mythid)
609 edhill 1.14 STOP 'ABNORMAL END: S/R MNC_CW_RX_R'
610 edhill 1.5 ENDIF
611     igrid = mnc_cw_vgind(ind_vt)
612    
613     C Check for bi,bj indicies
614 edhill 1.6 bidim = mnc_cw_vbij(1,ind_vt)
615     bjdim = mnc_cw_vbij(2,ind_vt)
616 edhill 1.5
617     C Set the bi,bj indicies
618     bis = bi
619     bie = bi
620     IF (bi .LT. 1) THEN
621     bis = 1
622     bie = nSx
623     ENDIF
624     bjs = bj
625     bje = bj
626     IF (bj .LT. 1) THEN
627     bjs = 1
628     bje = nSy
629     ENDIF
630    
631     DO lbj = bjs,bje
632     DO lbi = bis,bie
633    
634     C Create the file name
635 edhill 1.9 CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)
636 edhill 1.5 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
637     n1 = IFNBLNK(fbname)
638     n2 = ILNBLNK(fbname)
639     ntot = n2 - n1 + 1
640     fname(1:ntot) = fbname(n1:n2)
641     ntot = ntot + 1
642     fname(ntot:ntot) = '.'
643     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
644     nfname = ntot+9
645 edhill 1.13
646     C Add the path to the file name
647     IF (mnc_use_indir) THEN
648     path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
649     npath = ILNBLNK(mnc_indir_str)
650     path_fname(1:npath) = mnc_indir_str(1:npath)
651     path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
652     fname(1:MNC_MAX_CHAR) = path_fname(1:MNC_MAX_CHAR)
653     nfname = npath + nfname
654     ENDIF
655 edhill 1.5
656 edhill 1.30 WRITE(fname_zs,'(2a,i4.4,a1,i6.6,a3)')
657     & mnc_indir_str(1:npath), fbname(n1:n2),
658     & 0, '.', uniq_tnum, '.nc'
659    
660     C The steps are:
661     C (1) open the file in a READ-ONLY mode,
662     C (2) get the var id for the current variable,
663     C (3) read the data, and then
664     C (4) close the file--theres no need to keep it open!
665 edhill 1.5
666 edhill 1.28 write(msgbuf,'(4a)') 'MNC_CW_RX_R: cannot open',
667     & ' file ''', fname(1:nfname), ''' in read-only mode'
668     err = NF_OPEN(fname, NF_NOWRITE, fid)
669 edhill 1.30 IF ( err .NE. NF_NOERR ) THEN
670     C If the initial open fails, try again using a name with a
671     C zero sequence number inserted
672     err = NF_OPEN(fname_zs, NF_NOWRITE, fid)
673     ENDIF
674 edhill 1.28 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
675    
676     write(msgbuf,'(6a)')
677     & 'MNC_CW_RX_R: cannot get id for variable ''',
678     & vtype(nvf:nvl), '''in file ''', fname(1:nfname), ''''
679     err = NF_INQ_VARID(fid, vtype, idv)
680     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
681 edhill 1.6
682     C Check that the current sNy,sNy values and the in-file values
683     C are compatible and WARN (only warn) if not
684 edhill 1.28 C f_sNx = -1
685     C f_sNy = -1
686     C err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNx',atype,alen)
687     C IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
688     C err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', f_sNx)
689     C CALL MNC_HANDLE_ERR(err,
690     C & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R',
691     C & myThid)
692     C ENDIF
693     C err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNy',atype,alen)
694     C IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
695     C err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', f_sNy)
696     C CALL MNC_HANDLE_ERR(err,
697     C & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R',
698     C & myThid)
699     C ENDIF
700     C IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
701     C write(msgbuf,'(5a)') 'MNC_CW_RX_R WARNING: the ',
702     C & 'attributes ''sNx'' and ''sNy'' within the file ''',
703     C & fname(1:nfname), ''' do not exist or do not match ',
704     C & 'the current sizes within the model'
705     C CALL print_error(msgbuf, mythid)
706     C ENDIF
707 edhill 1.5
708 edhill 1.6 C Check that the in-memory variable and the in-file variables
709     C are of compatible sizes
710 edhill 1.8 C ires = 1
711 edhill 1.9 C CALL MNC_CHK_VTYP_R_NCVAR( ind_vt,
712 edhill 1.8 C & indf, ind_fv_ids, indu, ires)
713     C IF (ires .LT. 0) THEN
714 edhill 1.14 C write(msgbuf,'(7a)') 'MNC_CW_RX_R WARNING: the sizes ',
715 edhill 1.8 C & 'of the in-program variable ''', vtype(nvf:nvl),
716     C & ''' and the corresponding variable within file ''',
717     C & fname(1:nfname), ''' are not compatible -- please ',
718     C & 'check the sizes'
719     C CALL print_error(msgbuf, mythid)
720 edhill 1.14 C STOP 'ABNORMAL END: S/R MNC_CW_RX_R'
721 edhill 1.8 C ENDIF
722 edhill 1.5
723 edhill 1.6 C Check for bi,bj indicies
724     bidim = mnc_cw_vbij(1,ind_vt)
725     bjdim = mnc_cw_vbij(2,ind_vt)
726    
727     C Set the dimensions for the in-memory array
728     ndim = mnc_cw_ndim(igrid)
729     k = mnc_cw_dims(1,igrid)
730     IF (k .GT. 0) THEN
731     p(1) = k
732     ELSE
733     p(1) = 1
734     ENDIF
735     DO i = 2,9
736     k = mnc_cw_dims(i,igrid)
737     IF (k .LT. 1) THEN
738     k = 1
739     ENDIF
740     IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
741     p(i) = nSx * p(i-1)
742     ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
743     p(i) = nSy * p(i-1)
744     ELSE
745     p(i) = k * p(i-1)
746     ENDIF
747     ENDDO
748    
749     C Set starting and ending indicies for the in-memory array and
750     C the unlimited dimension offset for the NetCDF array
751     DO i = 1,9
752     udo(i) = 0
753     s(i) = 1
754     e(i) = 1
755     IF (i .LE. ndim) THEN
756     s(i) = mnc_cw_is(i,igrid)
757     e(i) = mnc_cw_ie(i,igrid)
758     ENDIF
759     C Check for the unlimited dimension
760     IF ((i .EQ. ndim)
761     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
762     IF (indu .GT. 0) THEN
763     C Use the indu value
764     udo(i) = indu - 1
765 edhill 1.28 ELSE
766     C We need the current unlim dim size
767     write(msgbuf,'(5a)') 'MNC_CW_RX_R: getting the ',
768     & 'unlim dim id within file ''',
769     & fname(1:nfname), ''''
770     err = NF_INQ_UNLIMDIM(fid, unlid)
771     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
772     write(msgbuf,'(5a)') 'MNC_CW_RX_R: getting the ',
773     & 'unlim dim size within file ''',
774     & fname(1:nfname), ''''
775     err = NF_INQ_DIMLEN(fid, unlid, unlim_sz)
776     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
777 edhill 1.6 udo(i) = unlim_sz
778     ENDIF
779     ENDIF
780     ENDDO
781     IF (bidim .GT. 0) THEN
782     s(bidim) = lbi
783     e(bidim) = lbi
784     ENDIF
785     IF (bjdim .GT. 0) THEN
786     s(bjdim) = lbj
787     e(bjdim) = lbj
788     ENDIF
789    
790 edhill 1.8 C DO i = 9,1,-1
791     C write(*,*) 'i,p(i),s(i),e(i) = ', i,': ',p(i),s(i),e(i)
792     C ENDDO
793 edhill 1.6
794     write(msgbuf,'(5a)') 'reading variable type ''',
795     & vtype(nvf:nvl), ''' within file ''',
796     & fname(1:nfname), ''''
797    
798     C Read the variable one vector at a time
799     DO j7 = s(7),e(7)
800     k7 = (j7 - 1)*p(6)
801     vstart(7) = udo(7) + j7 - s(7) + 1
802     vcount(7) = 1
803     DO j6 = s(6),e(6)
804     k6 = (j6 - 1)*p(5) + k7
805     vstart(6) = udo(6) + j6 - s(6) + 1
806     vcount(6) = 1
807     DO j5 = s(5),e(5)
808     k5 = (j5 - 1)*p(4) + k6
809     vstart(5) = udo(5) + j5 - s(5) + 1
810     vcount(5) = 1
811     DO j4 = s(4),e(4)
812     k4 = (j4 - 1)*p(3) + k5
813     vstart(4) = udo(4) + j4 - s(4) + 1
814     vcount(4) = 1
815     DO j3 = s(3),e(3)
816     k3 = (j3 - 1)*p(2) + k4
817     vstart(3) = udo(3) + j3 - s(3) + 1
818     vcount(3) = 1
819     DO j2 = s(2),e(2)
820     k2 = (j2 - 1)*p(1) + k3
821     vstart(2) = udo(2) + j2 - s(2) + 1
822     vcount(2) = 1
823    
824 edhill 1.14 kr = 0
825 edhill 1.6 vstart(1) = udo(1) + 1
826     vcount(1) = e(1) - s(1) + 1
827 edhill 1.24
828     IF (vcount(1) .GT. MNC_MAX_BUFF) THEN
829     write(msgbuf,'(2a,I7,a)') 'MNC_MAX_BUFF is too small',
830     & '--please increase to at least ',
831     & vcount(1), ' in ''MNC_SIZE.h'''
832     CALL PRINT_ERROR(msgBuf , 1)
833     STOP 'ABNORMAL END: S/R MNC_CW_RX_R_OFFSET'
834     ENDIF
835    
836 edhill 1.14 IF (stype(1:1) .EQ. 'D') THEN
837     err = NF_GET_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
838     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
839     DO j1 = s(1),e(1)
840     k1 = k2 + j1
841     kr = kr + 1
842 edhill 1.29 var(k1) = MNCI2( resh_d(kr) )
843 edhill 1.14 ENDDO
844     ENDIF
845     IF (stype(1:1) .EQ. 'R') THEN
846     err = NF_GET_VARA_REAL(fid, idv, vstart, vcount, resh_r)
847     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
848     DO j1 = s(1),e(1)
849     k1 = k2 + j1
850     kr = kr + 1
851 edhill 1.29 var(k1) = MNCI2( resh_r(kr) )
852 edhill 1.14 ENDDO
853     ENDIF
854     IF (stype(1:1) .EQ. 'I') THEN
855     err = NF_GET_VARA_INT(fid, idv, vstart, vcount, resh_i)
856     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
857     DO j1 = s(1),e(1)
858     k1 = k2 + j1
859     kr = kr + 1
860     var(k1) = resh_i(kr)
861     ENDDO
862     ENDIF
863 edhill 1.6
864    
865     ENDDO
866     ENDDO
867     ENDDO
868     ENDDO
869     ENDDO
870     ENDDO
871 edhill 1.8
872     C Close the file
873 edhill 1.28 C CALL MNC_FILE_CLOSE(fname, myThid)
874     err = NF_CLOSE(fid)
875     write(msgbuf,'(3a)') 'MNC_CW_RX_R: cannot close file ''',
876     & fname(1:nfname), ''''
877     CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
878    
879 edhill 1.1
880 edhill 1.6 C End the lbj,lbi loops
881 edhill 1.1 ENDDO
882     ENDDO
883    
884     _END_MASTER( myThid )
885    
886     RETURN
887     END
888    
889     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
890    
891     CEH3 ;;; Local Variables: ***
892     CEH3 ;;; mode:fortran ***
893     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22