/[MITgcm]/MITgcm/pkg/mnc/mnc_cwrapper.F
ViewVC logotype

Annotation of /MITgcm/pkg/mnc/mnc_cwrapper.F

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


Revision 1.14 - (hide annotations) (download)
Tue Jul 6 03:55:53 2004 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
Changes since 1.13: +39 -16 lines
 o prepare diagnostics for MNC/NetCDF output
   - add Nrphys to MNC
   - encode KDIAG within GDIAG
   - add use_mdsio and use_mnc flags to data.diagnostics
   - start converting diagnostics to Protex format
   - mdsio-based output for hs94.cs-32x32x5 is *identical*

1 edhill 1.14 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_cwrapper.F,v 1.13 2004/04/05 06:01: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 edhill 1.12 CBOP 0
8 edhill 1.11 C !ROUTINE: MNC_CW_ADD_GNAME
9 edhill 1.1
10 edhill 1.11 C !INTERFACE:
11 edhill 1.2 SUBROUTINE MNC_CW_ADD_GNAME(
12 edhill 1.1 I name,
13     I ndim,
14     I dlens,
15     I dnames,
16 edhill 1.9 I inds_beg, inds_end,
17     I myThid )
18 edhill 1.1
19 edhill 1.11 C !DESCRIPTION:
20     C Add a grid name to the MNC convenience wrapper layer.
21    
22     C !USES:
23 edhill 1.1 implicit none
24     #include "mnc_common.h"
25     #include "EEPARAMS.h"
26    
27 edhill 1.11 C !INPUT PARAMETERS:
28 edhill 1.1 integer myThid, ndim
29     character*(*) name
30     integer dlens(*), inds_beg(*), inds_end(*)
31     character*(*) dnames(*)
32 edhill 1.12 CEOP
33 edhill 1.1
34 edhill 1.11 C !LOCAL VARIABLES:
35     integer i, nnf,nnl, indg
36     character*(MAX_LEN_MBUF) msgbuf
37 edhill 1.12
38 edhill 1.2 C Functions
39     integer IFNBLNK, ILNBLNK
40    
41 edhill 1.1 nnf = IFNBLNK(name)
42     nnl = ILNBLNK(name)
43    
44     C Check that this name is not already defined
45 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, name, mnc_cw_gname, indg, myThid)
46 edhill 1.1 IF (indg .GT. 0) THEN
47 edhill 1.2 write(msgbuf,'(3a)') 'MNC_CW_ADD_GNAME ERROR: ''', name,
48 edhill 1.1 & ''' is already defined'
49     CALL print_error(msgbuf, mythid)
50 edhill 1.2 stop 'ABNORMAL END: S/R MNC_CW_ADD_GNAME'
51 edhill 1.1 ENDIF
52 edhill 1.9 CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_cw_gname,
53     & indg, myThid)
54 edhill 1.1
55 edhill 1.2 mnc_cw_gname(indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
56     mnc_cw_gname(indg)(1:(nnl-nnf+1)) = name(nnf:nnl)
57 edhill 1.1 mnc_cw_ndim(indg) = ndim
58    
59     DO i = 1,ndim
60     mnc_cw_dn(i,indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
61     nnf = IFNBLNK(dnames(i))
62     nnl = ILNBLNK(dnames(i))
63     mnc_cw_dn(i,indg)(1:(nnl-nnf+1)) = dnames(i)(nnf:nnl)
64     mnc_cw_dims(i,indg) = dlens(i)
65     mnc_cw_is(i,indg) = inds_beg(i)
66     mnc_cw_ie(i,indg) = inds_end(i)
67     ENDDO
68    
69     RETURN
70     END
71    
72 edhill 1.2 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
73 edhill 1.12 CBOP 1
74 edhill 1.11 C !ROUTINE: MNC_CW_DUMP
75 edhill 1.2
76 edhill 1.11 C !INTERFACE:
77 edhill 1.10 SUBROUTINE MNC_CW_DUMP( myThid )
78 edhill 1.2
79 edhill 1.11 C !DESCRIPTION:
80     C Write a condensed view of the current state of the MNC look-up
81     C tables for the convenience wrapper section.
82    
83     C !USES:
84 edhill 1.2 implicit none
85     #include "mnc_common.h"
86 edhill 1.10 #include "SIZE.h"
87     #include "EEPARAMS.h"
88     #include "PARAMS.h"
89    
90 edhill 1.11 C !INPUT PARAMETERS:
91 edhill 1.10 integer myThid
92 edhill 1.12 CEOP
93 edhill 1.2
94 edhill 1.11 C !LOCAL VARIABLES:
95 edhill 1.2 integer i,j, ntot
96 edhill 1.10 integer NBLNK
97     parameter ( NBLNK = 150 )
98     character s1*(NBLNK), blnk*(NBLNK)
99    
100     _BEGIN_MASTER(myThid)
101    
102     DO i = 1,NBLNK
103     blnk(i:i) = ' '
104     ENDDO
105    
106     s1(1:NBLNK) = blnk(1:NBLNK)
107     write(s1,'(a5,a)') 'MNC: ',
108     & 'The currently defined Grid Types are:'
109     CALL PRINT_MESSAGE(
110     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
111 edhill 1.2 ntot = 0
112     DO j = 1,MNC_MAX_ID
113     IF (mnc_cw_gname(j)(1:MNC_MAX_CHAR)
114     & .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
115    
116     ntot = ntot + 1
117 edhill 1.10 s1(1:NBLNK) = blnk(1:NBLNK)
118 edhill 1.14 write(s1,'(a5,2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a8)')
119 edhill 1.10 & 'MNC: ',
120 edhill 1.2 & j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),
121     & ' : ', (mnc_cw_dims(i,j), i=1,5),
122     & ' | ', (mnc_cw_is(i,j), i=1,5),
123     & ' | ', (mnc_cw_ie(i,j), i=1,5),
124 edhill 1.14 & ' | ', (mnc_cw_dn(i,j)(1:7), i=1,5)
125 edhill 1.10 CALL PRINT_MESSAGE(
126     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
127    
128 edhill 1.2 ENDIF
129     ENDDO
130 edhill 1.10
131     s1(1:NBLNK) = blnk(1:NBLNK)
132     write(s1,'(a5,a)') 'MNC: ',
133     & 'The currently defined Variable Types are:'
134     CALL PRINT_MESSAGE(
135     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
136 edhill 1.3 ntot = 0
137     DO j = 1,MNC_MAX_ID
138     IF (mnc_cw_vname(j)(1:MNC_MAX_CHAR)
139     & .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
140 edhill 1.10
141 edhill 1.3 ntot = ntot + 1
142 edhill 1.10 s1(1:NBLNK) = blnk(1:NBLNK)
143     write(s1,'(a5,2i5,a3,a25,a3,i4)') 'MNC: ',
144     & j, ntot, ' | ',
145     & mnc_cw_vname(j)(1:20), ' | ', mnc_cw_vgind(j)
146     CALL PRINT_MESSAGE(
147     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
148    
149 edhill 1.3 DO i = 1,mnc_cw_vnat(1,j)
150 edhill 1.10 s1(1:NBLNK) = blnk(1:NBLNK)
151     write(s1,'(a5,a14,i4,a3,a25,a3,a55)')
152     & 'MNC: ',' text_at:',i,
153 edhill 1.3 & ' : ', mnc_cw_vtnm(i,j)(1:25), ' : ',
154 edhill 1.8 & mnc_cw_vtat(i,j)(1:55)
155 edhill 1.10 CALL PRINT_MESSAGE(
156     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
157 edhill 1.3 ENDDO
158     DO i = 1,mnc_cw_vnat(2,j)
159 edhill 1.10 s1(1:NBLNK) = blnk(1:NBLNK)
160     write(s1,'(a5,a14,i4,a3,a25,a3,i20)')
161     & 'MNC: ',' int__at:',i,
162 edhill 1.3 & ' : ', mnc_cw_vinm(i,j)(1:25), ' : ',
163     & mnc_cw_viat(i,j)
164 edhill 1.10 CALL PRINT_MESSAGE(
165     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
166 edhill 1.3 ENDDO
167     DO i = 1,mnc_cw_vnat(3,j)
168 edhill 1.10 s1(1:NBLNK) = blnk(1:NBLNK)
169     write(s1,'(a5,a14,i4,a3,a25,a3,f25.10)')
170     & 'MNC: ',' dbl__at:',i,
171 edhill 1.3 & ' : ', mnc_cw_vdnm(i,j)(1:25), ' : ',
172     & mnc_cw_vdat(i,j)
173 edhill 1.10 CALL PRINT_MESSAGE(
174     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
175     ENDDO
176    
177 edhill 1.3 ENDIF
178     ENDDO
179     IF (ntot .EQ. 0) THEN
180 edhill 1.10 s1(1:NBLNK) = blnk(1:NBLNK)
181     write(s1,'(a)') 'MNC: None defined!'
182     CALL PRINT_MESSAGE(
183     & s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
184 edhill 1.3 ENDIF
185 edhill 1.10
186     _END_MASTER(myThid)
187 edhill 1.3
188 edhill 1.2 RETURN
189     END
190 edhill 1.1
191     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
192 edhill 1.12 CBOP 0
193 edhill 1.11 C !ROUTINE: MNC_CW_INIT
194 edhill 1.1
195 edhill 1.11 C !INTERFACE:
196 edhill 1.1 SUBROUTINE MNC_CW_INIT(
197 edhill 1.14 I sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr, NrPhys,
198 edhill 1.9 I myThid )
199 edhill 1.1
200 edhill 1.11 C !DESCRIPTION:
201 edhill 1.12 C Create the pre-defined grid types and variable types.
202    
203     C The grid type is a character string that encodes the presence and
204     C types associated with the four possible dimensions. The character
205     C string follows the format
206     C \begin{center}
207     C \texttt{H0\_H1\_H2\_\_V\_\_T}
208     C \end{center}
209     C where the terms \textit{H0}, \textit{H1}, \textit{H2}, \textit{V},
210     C \textit{T} can be almost any combination of the following:
211     C \begin{center}
212     C \begin{tabular}[h]{|ccc|c|c|}\hline
213     C \multicolumn{3}{|c|}{Horizontal} & Vertical & Time \\
214     C \textit{H0}: location & \textit{H1}: dimensions & \textit{H2}: halo
215     C & \textit{V}: location & \textit{T}: level \\\hline
216     C \texttt{-} & xy & Hn & \texttt{-} & \texttt{-} \\
217     C U & x & Hy & i & t \\
218     C V & y & & c & \\
219     C Cen & & & & \\
220     C Cor & & & & \\\hline
221     C \end{tabular}
222     C \end{center}
223    
224    
225 edhill 1.11 C !USES:
226 edhill 1.1 implicit none
227     #include "mnc_common.h"
228     #include "EEPARAMS.h"
229    
230 edhill 1.11 C !INPUT PARAMETERS:
231 edhill 1.1 integer myThid
232     integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr
233 edhill 1.14 integer NrPhys
234 edhill 1.12 CEOP
235 edhill 1.1
236 edhill 1.11 C !LOCAL VARIABLES:
237 edhill 1.1 integer CW_MAX_LOC
238     parameter ( CW_MAX_LOC = 5 )
239 edhill 1.2 integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot
240 edhill 1.14 integer ndim, ncomb, nvch, NrPh
241 edhill 1.1 character*(MNC_MAX_CHAR) name
242     character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)
243     character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),
244     & vert_dat(CW_MAX_LOC), time_dat(CW_MAX_LOC),
245     & halo_dat(CW_MAX_LOC)
246     integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)
247 edhill 1.12
248 edhill 1.11 C Functions
249 edhill 1.14 integer ILNBLNK
250     external ILNBLNK
251 edhill 1.1
252     C ......12345....12345....12345....12345....12345...
253     data horz_dat /
254     & '- ', 'U ', 'V ', 'Cen ', 'Cor ' /
255     data hsub_dat /
256     & 'xy ', 'x ', 'y ', '- ', ' ' /
257 edhill 1.2 data halo_dat /
258     & 'Hn ', 'Hy ', '-- ', ' ', ' ' /
259 edhill 1.1 data vert_dat /
260 edhill 1.14 & '- ', 'C ', 'I ', 'Phys ', 'PhysI' /
261 edhill 1.1 data time_dat /
262     & '- ', 't ', ' ', ' ', ' ' /
263    
264 edhill 1.14 if (NrPhys .lt. 1) then
265     NrPh = Nr
266     else
267     NrPh = NrPhys
268     endif
269    
270 edhill 1.2 ncomb = 0
271 edhill 1.1 DO ihorz = 1,5
272     DO is = 1,3
273 edhill 1.2 DO ih = 1,2
274    
275     C Loop just ONCE if the Horiz component is "-"
276     ihsub = is
277     ihalo = ih
278     IF (ihorz .EQ. 1) THEN
279     IF ((is .EQ. 1) .AND. (ih .EQ. 1)) THEN
280     ihsub = 4
281     ihalo = 3
282     ELSE
283     GOTO 10
284     ENDIF
285 edhill 1.1 ENDIF
286 edhill 1.2
287 edhill 1.14 DO ivert = 1,5
288 edhill 1.2 DO itime = 1,2
289    
290 edhill 1.1 C horiz and hsub
291     name(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
292     n = ILNBLNK(horz_dat(ihorz))
293     name(1:n) = horz_dat(ihorz)(1:n)
294     ntot = n + 1
295     name(ntot:ntot) = '_'
296     n = ILNBLNK(hsub_dat(ihsub))
297     name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)
298     ntot = ntot + n
299    
300 edhill 1.14 C halo, vert, and time
301     write(name((ntot+1):(ntot+5)), '(a1,2a2)')
302     & '_', halo_dat(ihalo)(1:2), '__'
303     nvch = ILNBLNK(vert_dat(ivert))
304     n = ntot+6+nvch-1
305     name((ntot+6):(n)) = vert_dat(ivert)(1:nvch)
306     write(name((n+1):(n+3)), '(a2,a1)')
307     & '__', time_dat(itime)(1:1)
308 edhill 1.1
309     ndim = 0
310     DO i = 1,CW_MAX_LOC
311     dn(i)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
312     dim(i) = 0
313 edhill 1.2 ib(i) = 0
314     ie(i) = 0
315 edhill 1.1 ENDDO
316    
317     C Horizontal dimensions
318     IF (halo_dat(ihalo)(1:5) .EQ. 'Hn ') THEN
319    
320     IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
321     ndim = ndim + 1
322     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
323     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
324     dn(ndim)(1:1) = 'X'
325     dim(ndim) = sNx + 2*OLx
326     ib(ndim) = OLx + 1
327     ie(ndim) = OLx + sNx
328     ENDIF
329     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
330     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
331     dn(ndim)(1:3) = 'Xp1'
332     dim(ndim) = sNx + 2*OLx
333     ib(ndim) = OLx + 1
334     ie(ndim) = OLx + sNx + 1
335     ENDIF
336     ENDIF
337     IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
338     & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
339     ndim = ndim + 1
340     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
341     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
342     dn(ndim)(1:1) = 'Y'
343     dim(ndim) = sNy + 2*OLy
344     ib(ndim) = OLy + 1
345     ie(ndim) = OLy + sNy
346     ENDIF
347     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
348     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
349     dn(ndim)(1:3) = 'Yp1'
350     dim(ndim) = sNy + 2*OLy
351     ib(ndim) = OLy + 1
352     ie(ndim) = OLy + sNy + 1
353     ENDIF
354     ENDIF
355    
356     ELSEIF (halo_dat(ihalo)(1:5) .EQ. 'Hy ') THEN
357    
358     IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
359     ndim = ndim + 1
360     dn(ndim)(1:3) = 'Xwh'
361     dim(ndim) = sNx + 2*OLx
362     ib(ndim) = 1
363     ie(ndim) = sNx + 2*OLx
364     ENDIF
365     IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
366     & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
367     ndim = ndim + 1
368     dn(ndim)(1:3) = 'Ywh'
369     dim(ndim) = sNy + 2*OLy
370     ib(ndim) = 1
371 edhill 1.2 ie(ndim) = sNy + 2*OLy
372 edhill 1.1 ENDIF
373    
374     ENDIF
375    
376     C Vertical dimension
377     IF (vert_dat(ivert)(1:1) .EQ. 'C') THEN
378     ndim = ndim + 1
379     dn(ndim)(1:1) = 'Z'
380     dim(ndim) = Nr
381     ib(ndim) = 1
382     ie(ndim) = Nr
383     ENDIF
384     IF (vert_dat(ivert)(1:1) .EQ. 'I') THEN
385     ndim = ndim + 1
386     dn(ndim)(1:3) = 'Zp1'
387     dim(ndim) = Nr + 1
388     ib(ndim) = 1
389     ie(ndim) = Nr + 1
390     ENDIF
391 edhill 1.14 IF (vert_dat(ivert)(1:5) .EQ. 'Phys ') THEN
392     ndim = ndim + 1
393     dn(ndim)(1:5) = 'Zphys'
394     dim(ndim) = NrPh
395     ib(ndim) = 1
396     ie(ndim) = NrPh
397     ENDIF
398     IF (vert_dat(ivert)(1:5) .EQ. 'PhysI') THEN
399     ndim = ndim + 1
400     dn(ndim)(1:7) = 'Zphysm1'
401     dim(ndim) = NrPh - 1
402     ib(ndim) = 1
403     ie(ndim) = NrPh - 1
404     ENDIF
405 edhill 1.1
406     C Time dimension
407     IF (time_dat(itime)(1:1) .EQ. 't') THEN
408     ndim = ndim + 1
409     dn(ndim)(1:1) = 'T'
410     dim(ndim) = -1
411     ib(ndim) = 1
412     ie(ndim) = 1
413     ENDIF
414    
415 edhill 1.2 IF (ndim .GT. 0) THEN
416     #ifdef MNC_DEBUG
417     ncomb = ncomb + 1
418     write(*,'(i4,a3,a15,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')
419     & ncomb, ' : ', name(1:15), ndim,
420     & ' : ', (dim(i), i=1,5),
421     & ' | ', (ib(i), i=1,5),
422     & ' | ', (ie(i), i=1,5),
423     & ' | ', (dn(i)(1:4), i=1,5)
424     #endif
425 edhill 1.1
426 edhill 1.9 CALL MNC_CW_ADD_GNAME(name, ndim,
427     & dim, dn, ib, ie, myThid)
428 edhill 1.1 ENDIF
429    
430     ENDDO
431     ENDDO
432 edhill 1.2
433     10 CONTINUE
434 edhill 1.1 ENDDO
435     ENDDO
436     ENDDO
437    
438 edhill 1.2 RETURN
439     END
440    
441     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
442 edhill 1.12 CBOP 0
443 edhill 1.13 C !ROUTINE: MNC_CW_APPEND_VNAME
444    
445     C !INTERFACE:
446     SUBROUTINE MNC_CW_APPEND_VNAME(
447     I vname,
448     I gname,
449     I bi_dim, bj_dim,
450     I myThid )
451    
452     C !DESCRIPTION:
453     C If it is not yet defined within the MNC CW layer, append a
454     C variable type. Calls MNC\_CW\_ADD\_VNAME().
455    
456     C !USES:
457     implicit none
458     #include "mnc_common.h"
459    
460     C !INPUT PARAMETERS:
461     integer myThid, bi_dim, bj_dim
462     character*(*) vname, gname
463     CEOP
464    
465     C !LOCAL VARIABLES:
466     integer indv
467    
468     C Check whether vname is defined
469     CALL MNC_GET_IND(MNC_MAX_ID, vname, mnc_cw_vname, indv, myThid)
470     IF (indv .LT. 1) THEN
471     CALL MNC_CW_ADD_VNAME(vname, gname, bi_dim, bj_dim, myThid)
472     ENDIF
473    
474    
475     RETURN
476     END
477    
478     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
479     CBOP 0
480 edhill 1.11 C !ROUTINE: MNC_CW_ADD_VNAME
481 edhill 1.2
482 edhill 1.11 C !INTERFACE:
483 edhill 1.2 SUBROUTINE MNC_CW_ADD_VNAME(
484     I vname,
485 edhill 1.5 I gname,
486 edhill 1.9 I bi_dim, bj_dim,
487     I myThid )
488 edhill 1.2
489 edhill 1.13 C !DESCRIPTION:
490     C Add a variable type to the MNC CW layer. The variable type is an
491     C association between a variable type name and the following items:
492 edhill 1.12 C \begin{center}
493     C \begin{tabular}[h]{|ll|}\hline
494     C \textbf{Item} & \textbf{Purpose} \\\hline
495     C grid type & defines the in-memory arrangement \\
496     C \texttt{bi,bj} dimensions & tiling indices, if present \\\hline
497     C \end{tabular}
498     C \end{center}
499    
500 edhill 1.11 C !USES:
501 edhill 1.2 implicit none
502     #include "mnc_common.h"
503     #include "EEPARAMS.h"
504    
505 edhill 1.11 C !INPUT PARAMETERS:
506 edhill 1.5 integer myThid, bi_dim, bj_dim
507 edhill 1.2 character*(*) vname, gname
508 edhill 1.12 CEOP
509 edhill 1.2
510 edhill 1.11 C !LOCAL VARIABLES:
511     integer i, nvf,nvl, ngf,ngl, indv,indg
512     character*(MAX_LEN_MBUF) msgbuf
513 edhill 1.12
514 edhill 1.2 C Functions
515     integer IFNBLNK, ILNBLNK
516    
517     nvf = IFNBLNK(vname)
518     nvl = ILNBLNK(vname)
519     ngf = IFNBLNK(gname)
520     ngl = ILNBLNK(gname)
521    
522     C Check that this vname is not already defined
523 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, vname, mnc_cw_vname, indv, myThid)
524 edhill 1.2 IF (indv .GT. 0) THEN
525     write(msgbuf,'(3a)') 'MNC_CW_ADD_VNAME ERROR: ''',
526     & vname(nvf:nvl), ''' is already defined'
527     CALL print_error(msgbuf, mythid)
528     stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
529     ENDIF
530 edhill 1.9 CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_cw_vname,
531     & indv, myThid)
532 edhill 1.2
533     C Check that gname exists
534 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, gname, mnc_cw_gname, indg, myThid)
535 edhill 1.2 IF (indg .LT. 1) THEN
536     write(msgbuf,'(3a)') 'MNC_CW_ADD_VNAME ERROR: ''',
537     & gname(ngf:ngl), ''' is not defined'
538     CALL print_error(msgbuf, mythid)
539     stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
540     ENDIF
541    
542     mnc_cw_vname(indv)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
543     mnc_cw_vname(indv)(1:(nvl-nvf+1)) = vname(nvf:nvl)
544     mnc_cw_vgind(indv) = indg
545     DO i = 1,3
546     mnc_cw_vnat(i,indv) = 0
547     ENDDO
548 edhill 1.5 mnc_cw_vbij(1,indv) = bi_dim
549     mnc_cw_vbij(2,indv) = bj_dim
550 edhill 1.6
551 edhill 1.9 CALL MNC_CW_ADD_VATTR_TEXT(vname,1,'mitgcm_grid',gname, myThid)
552 edhill 1.2
553     RETURN
554     END
555    
556     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
557 edhill 1.12 CBOP 0
558 edhill 1.11 C !ROUTINE: MNC_CW_ADD_VATTR_TEXT
559 edhill 1.2
560 edhill 1.11 C !INTERFACE:
561 edhill 1.3 SUBROUTINE MNC_CW_ADD_VATTR_TEXT(
562     I vname,
563     I ntat,
564     I tnames,
565 edhill 1.9 I tvals,
566     I myThid )
567 edhill 1.3
568 edhill 1.11 C !DESCRIPTION:
569     C Add a text attribute
570    
571     C !USES:
572 edhill 1.3 implicit none
573    
574 edhill 1.11 C !INPUT PARAMETERS:
575 edhill 1.3 integer myThid, ntat
576     character*(*) vname, tnames(*), tvals(*)
577 edhill 1.11 CEOP
578 edhill 1.3
579 edhill 1.9 CALL MNC_CW_ADD_VATTR_ANY(vname,
580 edhill 1.3 & ntat, 0, 0,
581     & tnames, ' ', ' ',
582 edhill 1.9 & tvals, 0, 0.0D0, myThid )
583 edhill 1.3
584     RETURN
585     END
586    
587     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
588 edhill 1.11 CBOP
589     C !ROUTINE: MNC_CW_ADD_VATTR_INT
590 edhill 1.3
591 edhill 1.11 C !INTERFACE:
592 edhill 1.3 SUBROUTINE MNC_CW_ADD_VATTR_INT(
593     I vname,
594     I niat,
595     I inames,
596 edhill 1.9 I ivals,
597     I myThid )
598 edhill 1.3
599 edhill 1.11 C !DESCRIPTION:
600    
601     C !USES:
602 edhill 1.3 implicit none
603    
604 edhill 1.11 C !INPUT PARAMETERS:
605 edhill 1.3 integer myThid, niat
606     character*(*) vname, inames(*)
607     integer ivals(*)
608 edhill 1.11 CEOP
609 edhill 1.3
610 edhill 1.9 CALL MNC_CW_ADD_VATTR_ANY(vname,
611 edhill 1.3 & 0, niat, 0,
612     & ' ', inames, ' ',
613 edhill 1.9 & ' ', ivals, 0.0D0, myThid )
614 edhill 1.3
615     RETURN
616     END
617    
618     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
619 edhill 1.12 CBOP 0
620 edhill 1.11 C !ROUTINE: MNC_CW_ADD_VATTR_DBL
621 edhill 1.3
622 edhill 1.11 C !INTERFACE:
623 edhill 1.3 SUBROUTINE MNC_CW_ADD_VATTR_DBL(
624     I vname,
625     I ndat,
626     I dnames,
627 edhill 1.9 I dvals,
628     I myThid )
629 edhill 1.3
630 edhill 1.11 C !DESCRIPTION:
631    
632     C !USES:
633 edhill 1.3 implicit none
634    
635 edhill 1.11 C !INPUT PARAMETERS:
636 edhill 1.3 integer myThid, ndat
637     character*(*) vname, dnames(*)
638     REAL*8 dvals(*)
639 edhill 1.11 CEOP
640 edhill 1.3
641 edhill 1.9 CALL MNC_CW_ADD_VATTR_ANY(vname,
642 edhill 1.3 & 0, 0, ndat,
643     & ' ', ' ', dnames,
644 edhill 1.9 & ' ', 0, dvals, myThid )
645 edhill 1.3
646     RETURN
647     END
648    
649     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
650 edhill 1.12 CBOP 1
651 edhill 1.11 C !ROUTINE: MNC_CW_ADD_VATTR_ANY
652 edhill 1.3
653 edhill 1.11 C !INTERFACE:
654 edhill 1.2 SUBROUTINE MNC_CW_ADD_VATTR_ANY(
655     I vname,
656     I ntat, niat, ndat,
657     I tnames, inames, dnames,
658 edhill 1.9 I tvals, ivals, dvals,
659     I myThid )
660 edhill 1.2
661 edhill 1.11 C !DESCRIPTION:
662    
663     C !USES:
664 edhill 1.2 implicit none
665     #include "mnc_common.h"
666     #include "EEPARAMS.h"
667    
668 edhill 1.11 C !INPUT PARAMETERS:
669 edhill 1.2 integer myThid, ntat, niat, ndat
670     character*(*) vname
671     character*(*) tnames(*), inames(*), dnames(*)
672     character*(*) tvals(*)
673     integer ivals(*)
674     REAL*8 dvals(*)
675 edhill 1.12 CEOP
676 edhill 1.2
677 edhill 1.11 C !LOCAL VARIABLES:
678     integer i, n, nvf,nvl, n1,n2, indv
679     character*(MAX_LEN_MBUF) msgbuf
680 edhill 1.12
681 edhill 1.2 C Functions
682     integer IFNBLNK, ILNBLNK
683    
684     nvf = IFNBLNK(vname)
685     nvl = ILNBLNK(vname)
686    
687     C Check that vname is defined
688 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, vname, mnc_cw_vname, indv, myThid)
689 edhill 1.2 IF (indv .LT. 1) THEN
690     write(msgbuf,'(3a)') 'MNC_CW_ADD_VATTR_ANY ERROR: ''',
691     & vname(nvf:nvl), ''' is not defined'
692     CALL print_error(msgbuf, mythid)
693     stop 'ABNORMAL END: S/R MNC_CW_ADD_VATTR_ANY'
694     ENDIF
695    
696     C Text Attributes
697     n = mnc_cw_vnat(1,indv)
698     DO i = 1,ntat
699     n1 = IFNBLNK(tnames(i))
700     n2 = ILNBLNK(tnames(i))
701     mnc_cw_vtnm(n+i,indv)(1:(n2-n1+1)) = tnames(i)(n1:n2)
702     n1 = IFNBLNK(tvals(i))
703     n2 = ILNBLNK(tvals(i))
704     mnc_cw_vtat(n+i,indv)(1:(n2-n1+1)) = tvals(i)(n1:n2)
705     ENDDO
706     mnc_cw_vnat(1,indv) = n + ntat
707    
708     C Integer Attributes
709     n = mnc_cw_vnat(2,indv)
710     DO i = 1,niat
711     n1 = IFNBLNK(inames(i))
712     n2 = ILNBLNK(inames(i))
713     mnc_cw_vinm(n+i,indv)(1:(n2-n1+1)) = inames(i)(n1:n2)
714     mnc_cw_viat(n+i,indv) = ivals(i)
715     ENDDO
716     mnc_cw_vnat(2,indv) = n + niat
717    
718     C Double Attributes
719     n = mnc_cw_vnat(3,indv)
720     DO i = 1,ndat
721     n1 = IFNBLNK(dnames(i))
722     n2 = ILNBLNK(dnames(i))
723     mnc_cw_vdnm(n+i,indv)(1:(n2-n1+1)) = dnames(i)(n1:n2)
724     mnc_cw_vdat(n+i,indv) = dvals(i)
725     ENDDO
726     mnc_cw_vnat(3,indv) = n + ndat
727 edhill 1.3
728     RETURN
729     END
730    
731     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
732 edhill 1.12 CBOP 1
733 edhill 1.11 C !ROUTINE: MNC_CW_GET_TILE_NUM
734 edhill 1.3
735 edhill 1.11 C !INTERFACE:
736 edhill 1.3 SUBROUTINE MNC_CW_GET_TILE_NUM(
737     I bi, bj,
738 edhill 1.9 O uniq_tnum,
739     I myThid )
740 edhill 1.3
741 edhill 1.11 C !DESCRIPTION:
742    
743     C !USES:
744 edhill 1.3 implicit none
745     #include "EEPARAMS.h"
746     #include "SIZE.h"
747 edhill 1.7 #ifdef ALLOW_EXCH2
748     #include "W2_EXCH2_TOPOLOGY.h"
749     #include "W2_EXCH2_PARAMS.h"
750     #endif
751 edhill 1.3
752 edhill 1.11 C !INPUT PARAMETERS:
753 edhill 1.3 integer myThid, bi,bj, uniq_tnum
754 edhill 1.12 CEOP
755 edhill 1.3
756 edhill 1.11 C !LOCAL VARIABLES:
757 edhill 1.3 integer iG,jG
758    
759 edhill 1.4 iG = 0
760     jG = 0
761    
762 edhill 1.3 #ifdef ALLOW_EXCH2
763    
764     uniq_tnum = W2_myTileList(bi)
765    
766     #else
767    
768     C Global tile number for simple (non-cube) domains
769     iG = bi+(myXGlobalLo-1)/sNx
770     jG = bj+(myYGlobalLo-1)/sNy
771 edhill 1.4
772     uniq_tnum = (jG - 1)*(nPx*nSx) + iG
773 edhill 1.3
774     #endif
775    
776 edhill 1.4 CEH3 write(*,*) 'iG,jG,uniq_tnum :', iG,jG,uniq_tnum
777    
778 edhill 1.3 RETURN
779     END
780    
781     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
782 edhill 1.12 CBOP 1
783 edhill 1.11 C !ROUTINE: MNC_CW_FILE_AORC
784    
785     C !INTERFACE:
786 edhill 1.3 SUBROUTINE MNC_CW_FILE_AORC(
787 edhill 1.4 I fname,
788 edhill 1.9 O indf,
789     I myThid )
790 edhill 1.3
791 edhill 1.11 C !DESCRIPTION:
792 edhill 1.13 C Open a NetCDF file, appending to the file if it already exists
793     C and, if not, creating a new file.
794 edhill 1.11
795     C !USES:
796 edhill 1.3 implicit none
797     #include "netcdf.inc"
798     #include "mnc_common.h"
799     #include "EEPARAMS.h"
800    
801 edhill 1.11 C !INPUT PARAMETERS:
802 edhill 1.4 integer myThid, indf
803 edhill 1.3 character*(*) fname
804 edhill 1.12 CEOP
805 edhill 1.3
806 edhill 1.11 C !LOCAL VARIABLES:
807 edhill 1.14 integer ierr
808 edhill 1.3
809     C Check if the file is already open
810 edhill 1.9 CALL MNC_GET_IND(MNC_MAX_ID, fname, mnc_f_names, indf, myThid)
811 edhill 1.3 IF (indf .GT. 0) THEN
812     RETURN
813     ENDIF
814    
815     C Try to open an existing file
816 edhill 1.9 CALL MNC_FILE_TRY_READ(fname, ierr, indf, myThid)
817 edhill 1.3 IF (ierr .EQ. NF_NOERR) THEN
818     RETURN
819     ENDIF
820    
821     C Try to create a new one
822 edhill 1.9 CALL MNC_FILE_OPEN(fname, 0, indf, myThid)
823 edhill 1.2
824 edhill 1.1 RETURN
825     END
826    
827     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
828    

  ViewVC Help
Powered by ViewVC 1.1.22