/[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.2 - (hide annotations) (download)
Wed Feb 4 05:45:09 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.1: +133 -23 lines
 o working (though incomplete) version of the "wrapper":
   - 149 pre-defined grids:
     - all "meaningful" X,Y,Z,T combinations
     - X,Y with or without halos
     - Horiz: centered, U, V, and corner (vorticity) grids
     - Vert: centered or interface
   - just two function calls to write a variable using one of the
     pre-defined grids
 o tile numbering scheme for both cube and XY grids
 o read, write, and append NetCDF files
 o checks for (acceptable) re-definition of dims, grids, and vars
 o numerous small bug fixes
 o warning: the two mnc_model_* files are now broken/obsolete and
   will soon be removed

1 edhill 1.2 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.1 2004/01/31 04:13:09 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     SUBROUTINE MNC_CW_RX_WRITES_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 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.2 integer i,j, 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
36     integer p(9),s(9),e(9), dimnc(9), vstart(9),vcount(9), kr
37     integer j1,j2,j3,j4,j5, k1,k2,k3,k4,k5
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     stop 'ABNORMAL END: S/R MNC_CW_RX_WRITES_YY'
62     ENDIF
63 edhill 1.2 igrid = mnc_cw_vgind(indv)
64 edhill 1.1
65 edhill 1.2 bis = bi
66     bie = bi
67 edhill 1.1 IF (bi .LT. 1) THEN
68     bis = 1
69     bie = nSx
70     ENDIF
71 edhill 1.2 bjs = bj
72     bje = bj
73 edhill 1.1 IF (bj .LT. 1) THEN
74     bjs = 1
75     bje = nSy
76     ENDIF
77    
78 edhill 1.2 DO lbj = bjs,bje
79     DO lbi = bis,bie
80 edhill 1.1
81     C Create the file name
82 edhill 1.2 CALL MNC_CW_GET_TILE_NUM(myThid, lbi,lbj, uniq_tnum)
83 edhill 1.1 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
84     n1 = IFNBLNK(fbname)
85     n2 = ILNBLNK(fbname)
86     ntot = n2 - n1 + 1
87     fname(1:ntot) = fbname(n1:n2)
88     ntot = ntot + 1
89     fname(ntot:ntot) = '.'
90     write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
91 edhill 1.2 nfname = ntot+9
92    
93     C Append to an existing or create a new file
94     CALL MNC_CW_FILE_AORC(myThid, fname, indf)
95     fid = mnc_f_info(indf,2)
96    
97     C Ensure that all the NetCDF dims are defined and create a local
98     C copy
99     DO i = 1,9
100     dimnc(i) = 1
101     ENDDO
102     DO i = 1,mnc_cw_ndim(igrid)
103     dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
104     CALL MNC_DIM_INIT(myThid,fname,
105     & mnc_cw_dn(i,igrid), dimnc(i) )
106     ENDDO
107    
108     C Ensure that the "grid" is defined
109     CALL MNC_GRID_INIT(myThid,fname, mnc_cw_gname(igrid),
110     & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid))
111    
112     C Ensure that the variable is defined
113     #ifdef mnc_rtype_D
114     CALL MNC_VAR_INIT_DBL(myThid,fname,mnc_cw_gname(igrid),vtype)
115     #endif
116     #ifdef mnc_rtype_R
117     CALL MNC_VAR_INIT_REAL(myThid,fname,mnc_cw_gname(igrid),vtype)
118     #endif
119     DO i = 1,mnc_fv_ids(indf,1)
120     j = 2 + 3*(i - 1)
121     IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
122     idv = mnc_fv_ids(indf,j+1)
123     indvids = mnc_fd_ind(indf, mnc_f_info(indf,
124     & (mnc_fv_ids(indf,j+2) + 1)) )
125     GOTO 10
126     ENDIF
127     ENDDO
128     write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_WRITES_YY ERROR: ',
129     & 'cannot reference variable ''', vtype, ''''
130     CALL print_error(msgbuf, mythid)
131     stop 'ABNORMAL END: package MNC'
132     10 CONTINUE
133    
134     C Set the dimensions for the in-memory array
135     ndim = mnc_cw_ndim(igrid)
136     p(1) = mnc_cw_dims(1,igrid)
137     DO i = 2,9
138     p(i) = mnc_cw_dims(i,igrid) * p(i-1)
139     ENDDO
140    
141     C Set the starting and ending indicies
142     DO i = 1,9
143     IF (i .GT. ndim) THEN
144     s(i) = 1
145     e(i) = 1
146     ELSE
147     IF ((i .EQ. ndim)
148     & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
149     s(i) = indu
150     e(i) = indu
151     ELSE
152     s(i) = mnc_cw_is(i,igrid)
153     e(i) = mnc_cw_ie(i,igrid)
154     ENDIF
155     ENDIF
156     ENDDO
157    
158     CALL MNC_FILE_ENDDEF(myThid,fname)
159    
160     C Write the variable one vector at a time
161     DO j5 = s(5),e(5)
162     k5 = (j5 - s(5))*p(4)
163     vstart(5) = j5 - s(5) + 1
164     vcount(5) = 1
165     DO j4 = s(4),e(4)
166     k4 = (j4 - s(4))*p(3) + k5
167     vstart(4) = j4 - s(4) + 1
168     vcount(4) = 1
169     DO j3 = s(3),e(3)
170     k3 = (j3 - s(3))*p(2) + k4
171     vstart(3) = j3 - s(3) + 1
172     vcount(3) = 1
173     DO j2 = s(2),e(2)
174     k2 = (j2 - s(2))*p(1) + k3
175     vstart(2) = j2 - s(2) + 1
176     vcount(2) = 1
177    
178     kr = 0
179     DO j1 = s(1),e(1)
180     k1 = k2 + j1
181     kr = kr + 1
182     resh(kr) = var(k1)
183     ENDDO
184 edhill 1.1
185 edhill 1.2 vstart(1) = 1
186     vcount(1) = e(1) - s(1) + 1
187 edhill 1.1
188 edhill 1.2 CEH3 write(*,*) ' # ', j2,j3,j4,j5, ' # ',
189     CEH3 & (vstart(i),vcount(i),i=1,5)
190    
191     #ifdef mnc_rtype_D
192     err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
193     #endif
194     #ifdef mnc_rtype_R
195     err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh)
196     #endif
197 edhill 1.1
198 edhill 1.2 ENDDO
199     ENDDO
200     ENDDO
201     ENDDO
202    
203     C Sync the file
204     err = NF_SYNC(fid)
205     write(msgbuf,'(3a)') 'sync for file ''', fname,
206     & ''' in S/R MNC_CW_RX_WRITES_YY'
207     CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
208 edhill 1.1
209     ENDDO
210     ENDDO
211    
212     _END_MASTER( myThid )
213    
214     RETURN
215     END
216    
217     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
218    
219     CEH3 ;;; Local Variables: ***
220     CEH3 ;;; mode:fortran ***
221     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22