/[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.7 - (hide annotations) (download)
Mon Feb 16 22:21:43 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52j_post, checkpoint52k_post, checkpoint52j_pre
Changes since 1.6: +5 -2 lines
 o minor fixes for mnc with exch2
   - tested with global_ocean.cs32x15

1 edhill 1.7 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cwrapper.F,v 1.6 2004/02/05 05:42: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    
8 edhill 1.2 SUBROUTINE MNC_CW_ADD_GNAME(
9 edhill 1.1 I myThid,
10     I name,
11     I ndim,
12     I dlens,
13     I dnames,
14     I inds_beg, inds_end )
15    
16     implicit none
17     #include "mnc_common.h"
18     #include "EEPARAMS.h"
19    
20     C Arguments
21     integer myThid, ndim
22     character*(*) name
23     integer dlens(*), inds_beg(*), inds_end(*)
24     character*(*) dnames(*)
25    
26 edhill 1.2 C Functions
27     integer IFNBLNK, ILNBLNK
28    
29 edhill 1.1 C Local Variables
30     integer i, nnf,nnl, indg
31     character*(MAX_LEN_MBUF) msgbuf
32    
33     nnf = IFNBLNK(name)
34     nnl = ILNBLNK(name)
35    
36     C Check that this name is not already defined
37 edhill 1.2 CALL MNC_GET_IND(myThid, MNC_MAX_ID, name, mnc_cw_gname, indg)
38 edhill 1.1 IF (indg .GT. 0) THEN
39 edhill 1.2 write(msgbuf,'(3a)') 'MNC_CW_ADD_GNAME ERROR: ''', name,
40 edhill 1.1 & ''' is already defined'
41     CALL print_error(msgbuf, mythid)
42 edhill 1.2 stop 'ABNORMAL END: S/R MNC_CW_ADD_GNAME'
43 edhill 1.1 ENDIF
44 edhill 1.2 CALL MNC_GET_NEXT_EMPTY_IND(myThid, MNC_MAX_ID, mnc_cw_gname,
45 edhill 1.1 & indg)
46    
47 edhill 1.2 mnc_cw_gname(indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
48     mnc_cw_gname(indg)(1:(nnl-nnf+1)) = name(nnf:nnl)
49 edhill 1.1 mnc_cw_ndim(indg) = ndim
50    
51     DO i = 1,ndim
52     mnc_cw_dn(i,indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
53     nnf = IFNBLNK(dnames(i))
54     nnl = ILNBLNK(dnames(i))
55     mnc_cw_dn(i,indg)(1:(nnl-nnf+1)) = dnames(i)(nnf:nnl)
56     mnc_cw_dims(i,indg) = dlens(i)
57     mnc_cw_is(i,indg) = inds_beg(i)
58     mnc_cw_ie(i,indg) = inds_end(i)
59     ENDDO
60    
61     RETURN
62     END
63    
64 edhill 1.2 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65    
66     SUBROUTINE MNC_CW_DUMP()
67    
68     implicit none
69     #include "mnc_common.h"
70    
71     C Local Variables
72     integer i,j, ntot
73    
74 edhill 1.3 write(*,'(a)') 'The currently defined Grid Types are:'
75 edhill 1.2 ntot = 0
76     DO j = 1,MNC_MAX_ID
77     IF (mnc_cw_gname(j)(1:MNC_MAX_CHAR)
78     & .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
79    
80     ntot = ntot + 1
81     write(*,'(2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')
82     & j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),
83     & ' : ', (mnc_cw_dims(i,j), i=1,5),
84     & ' | ', (mnc_cw_is(i,j), i=1,5),
85     & ' | ', (mnc_cw_ie(i,j), i=1,5),
86     & ' | ', (mnc_cw_dn(i,j)(1:4), i=1,5)
87    
88     ENDIF
89     ENDDO
90    
91 edhill 1.3 write(*,'(a)') 'The currently defined Variable Types are:'
92     ntot = 0
93     DO j = 1,MNC_MAX_ID
94     IF (mnc_cw_vname(j)(1:MNC_MAX_CHAR)
95     & .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
96    
97     ntot = ntot + 1
98     write(*,'(2i5,a3,a25,a3,i4)') j, ntot, ' : ',
99     & mnc_cw_vname(j)(1:20), ' : ', mnc_cw_vgind(j)
100    
101     DO i = 1,mnc_cw_vnat(1,j)
102     write(*,'(a14,i4,a3,a25,a3,a25)') ' text_at:',i,
103     & ' : ', mnc_cw_vtnm(i,j)(1:25), ' : ',
104     & mnc_cw_vtat(i,j)(1:25)
105     ENDDO
106     DO i = 1,mnc_cw_vnat(2,j)
107     write(*,'(a14,i4,a3,a25,a3,i20)') ' int__at:',i,
108     & ' : ', mnc_cw_vinm(i,j)(1:25), ' : ',
109     & mnc_cw_viat(i,j)
110     ENDDO
111     DO i = 1,mnc_cw_vnat(3,j)
112     write(*,'(a14,i4,a3,a25,a3,f25.10)') ' dbl__at:',i,
113     & ' : ', mnc_cw_vdnm(i,j)(1:25), ' : ',
114     & mnc_cw_vdat(i,j)
115     ENDDO
116    
117     ENDIF
118     ENDDO
119     IF (ntot .EQ. 0) THEN
120     write(*,'(a)') ' None defined!'
121     ENDIF
122    
123    
124 edhill 1.2 RETURN
125     END
126 edhill 1.1
127     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
128    
129     SUBROUTINE MNC_CW_INIT(
130     I myThid,
131     I sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr )
132    
133     implicit none
134     #include "mnc_common.h"
135     #include "EEPARAMS.h"
136    
137     C Arguments
138     integer myThid
139     integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr
140    
141     C Functions
142     integer IFNBLNK, ILNBLNK
143    
144     C Local Variables
145     integer CW_MAX_LOC
146     parameter ( CW_MAX_LOC = 5 )
147 edhill 1.2 integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot
148     integer ndim, ncomb
149 edhill 1.1 character*(MAX_LEN_MBUF) msgbuf
150     character*(MNC_MAX_CHAR) name
151     character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)
152     character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),
153     & vert_dat(CW_MAX_LOC), time_dat(CW_MAX_LOC),
154     & halo_dat(CW_MAX_LOC)
155     integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)
156    
157     C ......12345....12345....12345....12345....12345...
158     data horz_dat /
159     & '- ', 'U ', 'V ', 'Cen ', 'Cor ' /
160     data hsub_dat /
161     & 'xy ', 'x ', 'y ', '- ', ' ' /
162 edhill 1.2 data halo_dat /
163     & 'Hn ', 'Hy ', '-- ', ' ', ' ' /
164 edhill 1.1 data vert_dat /
165     & '- ', 'C ', 'I ', ' ', ' ' /
166     data time_dat /
167     & '- ', 't ', ' ', ' ', ' ' /
168    
169 edhill 1.2 ncomb = 0
170 edhill 1.1 DO ihorz = 1,5
171     DO is = 1,3
172 edhill 1.2 DO ih = 1,2
173    
174     C Loop just ONCE if the Horiz component is "-"
175     ihsub = is
176     ihalo = ih
177     IF (ihorz .EQ. 1) THEN
178     IF ((is .EQ. 1) .AND. (ih .EQ. 1)) THEN
179     ihsub = 4
180     ihalo = 3
181     ELSE
182     GOTO 10
183     ENDIF
184 edhill 1.1 ENDIF
185 edhill 1.2
186     DO ivert = 1,3
187     DO itime = 1,2
188    
189 edhill 1.1 C horiz and hsub
190     name(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
191     n = ILNBLNK(horz_dat(ihorz))
192     name(1:n) = horz_dat(ihorz)(1:n)
193     ntot = n + 1
194     name(ntot:ntot) = '_'
195     n = ILNBLNK(hsub_dat(ihsub))
196     name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)
197     ntot = ntot + n
198    
199     C vert, time, and halo
200 edhill 1.2 write(name((ntot+1):(ntot+9)), '(a1,2a2,a1,a2,a1)')
201     & '_', halo_dat(ihalo)(1:2), '__',
202     & vert_dat(ivert)(1:1), '__',
203     & time_dat(itime)(1:1)
204 edhill 1.1
205     ndim = 0
206     DO i = 1,CW_MAX_LOC
207     dn(i)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
208     dim(i) = 0
209 edhill 1.2 ib(i) = 0
210     ie(i) = 0
211 edhill 1.1 ENDDO
212    
213     C Horizontal dimensions
214     IF (halo_dat(ihalo)(1:5) .EQ. 'Hn ') THEN
215    
216     IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
217     ndim = ndim + 1
218     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
219     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
220     dn(ndim)(1:1) = 'X'
221     dim(ndim) = sNx + 2*OLx
222     ib(ndim) = OLx + 1
223     ie(ndim) = OLx + sNx
224     ENDIF
225     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
226     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
227     dn(ndim)(1:3) = 'Xp1'
228     dim(ndim) = sNx + 2*OLx
229     ib(ndim) = OLx + 1
230     ie(ndim) = OLx + sNx + 1
231     ENDIF
232     ENDIF
233     IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
234     & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
235     ndim = ndim + 1
236     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
237     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
238     dn(ndim)(1:1) = 'Y'
239     dim(ndim) = sNy + 2*OLy
240     ib(ndim) = OLy + 1
241     ie(ndim) = OLy + sNy
242     ENDIF
243     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
244     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
245     dn(ndim)(1:3) = 'Yp1'
246     dim(ndim) = sNy + 2*OLy
247     ib(ndim) = OLy + 1
248     ie(ndim) = OLy + sNy + 1
249     ENDIF
250     ENDIF
251    
252     ELSEIF (halo_dat(ihalo)(1:5) .EQ. 'Hy ') THEN
253    
254     IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
255     ndim = ndim + 1
256     dn(ndim)(1:3) = 'Xwh'
257     dim(ndim) = sNx + 2*OLx
258     ib(ndim) = 1
259     ie(ndim) = sNx + 2*OLx
260     ENDIF
261     IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
262     & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
263     ndim = ndim + 1
264     dn(ndim)(1:3) = 'Ywh'
265     dim(ndim) = sNy + 2*OLy
266     ib(ndim) = 1
267 edhill 1.2 ie(ndim) = sNy + 2*OLy
268 edhill 1.1 ENDIF
269    
270     ENDIF
271    
272     C Vertical dimension
273     IF (vert_dat(ivert)(1:1) .EQ. 'C') THEN
274     ndim = ndim + 1
275     dn(ndim)(1:1) = 'Z'
276     dim(ndim) = Nr
277     ib(ndim) = 1
278     ie(ndim) = Nr
279     ENDIF
280     IF (vert_dat(ivert)(1:1) .EQ. 'I') THEN
281     ndim = ndim + 1
282     dn(ndim)(1:3) = 'Zp1'
283     dim(ndim) = Nr + 1
284     ib(ndim) = 1
285     ie(ndim) = Nr + 1
286     ENDIF
287    
288     C Time dimension
289     IF (time_dat(itime)(1:1) .EQ. 't') THEN
290     ndim = ndim + 1
291     dn(ndim)(1:1) = 'T'
292     dim(ndim) = -1
293     ib(ndim) = 1
294     ie(ndim) = 1
295     ENDIF
296    
297 edhill 1.2 IF (ndim .GT. 0) THEN
298     #ifdef MNC_DEBUG
299     ncomb = ncomb + 1
300     write(*,'(i4,a3,a15,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')
301     & ncomb, ' : ', name(1:15), ndim,
302     & ' : ', (dim(i), i=1,5),
303     & ' | ', (ib(i), i=1,5),
304     & ' | ', (ie(i), i=1,5),
305     & ' | ', (dn(i)(1:4), i=1,5)
306     #endif
307 edhill 1.1
308 edhill 1.2 CALL MNC_CW_ADD_GNAME(myThid, name, ndim,
309 edhill 1.1 & dim, dn, ib, ie)
310     ENDIF
311    
312     ENDDO
313     ENDDO
314 edhill 1.2
315     10 CONTINUE
316 edhill 1.1 ENDDO
317     ENDDO
318     ENDDO
319    
320 edhill 1.2 RETURN
321     END
322    
323     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
324    
325     SUBROUTINE MNC_CW_ADD_VNAME(
326     I myThid,
327     I vname,
328 edhill 1.5 I gname,
329     I bi_dim, bj_dim )
330 edhill 1.2
331     implicit none
332     #include "mnc_common.h"
333     #include "EEPARAMS.h"
334    
335     C Arguments
336 edhill 1.5 integer myThid, bi_dim, bj_dim
337 edhill 1.2 character*(*) vname, gname
338    
339     C Functions
340     integer IFNBLNK, ILNBLNK
341    
342     C Local Variables
343     integer i, nvf,nvl, ngf,ngl, indv,indg
344     character*(MAX_LEN_MBUF) msgbuf
345    
346     nvf = IFNBLNK(vname)
347     nvl = ILNBLNK(vname)
348     ngf = IFNBLNK(gname)
349     ngl = ILNBLNK(gname)
350    
351     C Check that this vname is not already defined
352     CALL MNC_GET_IND(myThid, MNC_MAX_ID, vname, mnc_cw_vname, indv)
353     IF (indv .GT. 0) THEN
354     write(msgbuf,'(3a)') 'MNC_CW_ADD_VNAME ERROR: ''',
355     & vname(nvf:nvl), ''' is already defined'
356     CALL print_error(msgbuf, mythid)
357     stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
358     ENDIF
359     CALL MNC_GET_NEXT_EMPTY_IND(myThid, MNC_MAX_ID, mnc_cw_vname,
360     & indv)
361    
362     C Check that gname exists
363     CALL MNC_GET_IND(myThid, MNC_MAX_ID, gname, mnc_cw_gname, indg)
364     IF (indg .LT. 1) THEN
365     write(msgbuf,'(3a)') 'MNC_CW_ADD_VNAME ERROR: ''',
366     & gname(ngf:ngl), ''' is not defined'
367     CALL print_error(msgbuf, mythid)
368     stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
369     ENDIF
370    
371     mnc_cw_vname(indv)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
372     mnc_cw_vname(indv)(1:(nvl-nvf+1)) = vname(nvf:nvl)
373     mnc_cw_vgind(indv) = indg
374     DO i = 1,3
375     mnc_cw_vnat(i,indv) = 0
376     ENDDO
377 edhill 1.5 mnc_cw_vbij(1,indv) = bi_dim
378     mnc_cw_vbij(2,indv) = bj_dim
379 edhill 1.6
380     CALL MNC_CW_ADD_VATTR_TEXT(myThid,vname,1,'mitgcm_grid',gname)
381 edhill 1.2
382     RETURN
383     END
384    
385     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
386    
387 edhill 1.3 SUBROUTINE MNC_CW_ADD_VATTR_TEXT(
388     I myThid,
389     I vname,
390     I ntat,
391     I tnames,
392     I tvals )
393    
394     implicit none
395    
396     C Arguments
397     integer myThid, ntat
398     character*(*) vname, tnames(*), tvals(*)
399    
400     CALL MNC_CW_ADD_VATTR_ANY(myThid, vname,
401     & ntat, 0, 0,
402     & tnames, ' ', ' ',
403     & tvals, 0, 0.0D0 )
404    
405     RETURN
406     END
407    
408     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
409    
410     SUBROUTINE MNC_CW_ADD_VATTR_INT(
411     I myThid,
412     I vname,
413     I niat,
414     I inames,
415     I ivals )
416    
417     implicit none
418    
419     C Arguments
420     integer myThid, niat
421     character*(*) vname, inames(*)
422     integer ivals(*)
423    
424     CALL MNC_CW_ADD_VATTR_ANY(myThid, vname,
425     & 0, niat, 0,
426     & ' ', inames, ' ',
427     & ' ', ivals, 0.0D0 )
428    
429     RETURN
430     END
431    
432     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
433    
434     SUBROUTINE MNC_CW_ADD_VATTR_DBL(
435     I myThid,
436     I vname,
437     I ndat,
438     I dnames,
439     I dvals )
440    
441     implicit none
442    
443     C Arguments
444     integer myThid, ndat
445     character*(*) vname, dnames(*)
446     REAL*8 dvals(*)
447    
448     CALL MNC_CW_ADD_VATTR_ANY(myThid, vname,
449     & 0, 0, ndat,
450     & ' ', ' ', dnames,
451     & ' ', 0, dvals )
452    
453     RETURN
454     END
455    
456     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
457    
458 edhill 1.2 SUBROUTINE MNC_CW_ADD_VATTR_ANY(
459     I myThid,
460     I vname,
461     I ntat, niat, ndat,
462     I tnames, inames, dnames,
463     I tvals, ivals, dvals )
464    
465     implicit none
466     #include "mnc_common.h"
467     #include "EEPARAMS.h"
468    
469     C Arguments
470     integer myThid, ntat, niat, ndat
471     character*(*) vname
472     character*(*) tnames(*), inames(*), dnames(*)
473     character*(*) tvals(*)
474     integer ivals(*)
475     REAL*8 dvals(*)
476    
477     C Functions
478     integer IFNBLNK, ILNBLNK
479    
480     C Local Variables
481     integer i, n, nvf,nvl, n1,n2, indv
482     character*(MAX_LEN_MBUF) msgbuf
483    
484     nvf = IFNBLNK(vname)
485     nvl = ILNBLNK(vname)
486    
487     C Check that vname is defined
488     CALL MNC_GET_IND(myThid, MNC_MAX_ID, vname, mnc_cw_vname, indv)
489     IF (indv .LT. 1) THEN
490     write(msgbuf,'(3a)') 'MNC_CW_ADD_VATTR_ANY ERROR: ''',
491     & vname(nvf:nvl), ''' is not defined'
492     CALL print_error(msgbuf, mythid)
493     stop 'ABNORMAL END: S/R MNC_CW_ADD_VATTR_ANY'
494     ENDIF
495    
496     C Text Attributes
497     n = mnc_cw_vnat(1,indv)
498     DO i = 1,ntat
499     n1 = IFNBLNK(tnames(i))
500     n2 = ILNBLNK(tnames(i))
501     mnc_cw_vtnm(n+i,indv)(1:(n2-n1+1)) = tnames(i)(n1:n2)
502     n1 = IFNBLNK(tvals(i))
503     n2 = ILNBLNK(tvals(i))
504     mnc_cw_vtat(n+i,indv)(1:(n2-n1+1)) = tvals(i)(n1:n2)
505     ENDDO
506     mnc_cw_vnat(1,indv) = n + ntat
507    
508     C Integer Attributes
509     n = mnc_cw_vnat(2,indv)
510     DO i = 1,niat
511     n1 = IFNBLNK(inames(i))
512     n2 = ILNBLNK(inames(i))
513     mnc_cw_vinm(n+i,indv)(1:(n2-n1+1)) = inames(i)(n1:n2)
514     mnc_cw_viat(n+i,indv) = ivals(i)
515     ENDDO
516     mnc_cw_vnat(2,indv) = n + niat
517    
518     C Double Attributes
519     n = mnc_cw_vnat(3,indv)
520     DO i = 1,ndat
521     n1 = IFNBLNK(dnames(i))
522     n2 = ILNBLNK(dnames(i))
523     mnc_cw_vdnm(n+i,indv)(1:(n2-n1+1)) = dnames(i)(n1:n2)
524     mnc_cw_vdat(n+i,indv) = dvals(i)
525     ENDDO
526     mnc_cw_vnat(3,indv) = n + ndat
527 edhill 1.3
528     RETURN
529     END
530    
531     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
532    
533     SUBROUTINE MNC_CW_GET_TILE_NUM(
534     I myThid,
535     I bi, bj,
536     O uniq_tnum )
537    
538     implicit none
539     #include "EEPARAMS.h"
540     #include "SIZE.h"
541 edhill 1.7 #ifdef ALLOW_EXCH2
542     #include "W2_EXCH2_TOPOLOGY.h"
543     #include "W2_EXCH2_PARAMS.h"
544     #endif
545 edhill 1.3
546     C Arguments
547     integer myThid, bi,bj, uniq_tnum
548    
549     C Local Variables
550     integer iG,jG
551    
552 edhill 1.4 iG = 0
553     jG = 0
554    
555 edhill 1.3 #ifdef ALLOW_EXCH2
556    
557     uniq_tnum = W2_myTileList(bi)
558    
559     #else
560    
561     C Global tile number for simple (non-cube) domains
562     iG = bi+(myXGlobalLo-1)/sNx
563     jG = bj+(myYGlobalLo-1)/sNy
564 edhill 1.4
565     uniq_tnum = (jG - 1)*(nPx*nSx) + iG
566 edhill 1.3
567     #endif
568    
569 edhill 1.4 CEH3 write(*,*) 'iG,jG,uniq_tnum :', iG,jG,uniq_tnum
570    
571 edhill 1.3 RETURN
572     END
573    
574     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
575    
576     SUBROUTINE MNC_CW_FILE_AORC(
577     I myThid,
578 edhill 1.4 I fname,
579     O indf )
580 edhill 1.3
581     implicit none
582     #include "netcdf.inc"
583     #include "mnc_common.h"
584     #include "EEPARAMS.h"
585    
586     C Arguments
587 edhill 1.4 integer myThid, indf
588 edhill 1.3 character*(*) fname
589    
590     C Local Variables
591 edhill 1.4 integer i, ierr
592 edhill 1.3 character*(MAX_LEN_MBUF) msgbuf
593    
594     C Check if the file is already open
595     CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, indf)
596     IF (indf .GT. 0) THEN
597     RETURN
598     ENDIF
599    
600     C Try to open an existing file
601 edhill 1.4 CALL MNC_FILE_TRY_READ(myThid, fname, ierr, indf)
602 edhill 1.3 IF (ierr .EQ. NF_NOERR) THEN
603     RETURN
604     ENDIF
605    
606     C Try to create a new one
607 edhill 1.4 CALL MNC_FILE_OPEN(myThid, fname, 0, indf)
608 edhill 1.2
609 edhill 1.1 RETURN
610     END
611    
612     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
613    

  ViewVC Help
Powered by ViewVC 1.1.22