/[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.18 - (hide annotations) (download)
Wed Sep 1 02:43:36 2004 UTC (19 years, 9 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint54e_post, checkpoint55b_post, checkpoint55, checkpoint54f_post, checkpoint55a_post
Changes since 1.17: +3 -1 lines
 o remove gtype attribute except for debugging

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

  ViewVC Help
Powered by ViewVC 1.1.22