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

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

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


Revision 1.13 - (show annotations) (download)
Mon Apr 5 06:01:07 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint54a_post, checkpoint53c_post, checkpoint53b_pre, checkpoint52m_post, checkpoint53a_post, checkpoint54, checkpoint53b_post, checkpoint53, checkpoint53g_post, checkpoint53f_post, checkpoint53d_pre
Changes since 1.12: +43 -4 lines
 o fix a serious memory-wasting bug in MNC_GRID_INIT_ALL()
 o give the "monitor" package the ability to write to NetCDF files
   - requested by JMC
   - tested and works but needs more run-time options

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

  ViewVC Help
Powered by ViewVC 1.1.22