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

1 edhill 1.4 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cwrapper.F,v 1.3 2004/01/31 04:13:09 edhill Exp $
2 edhill 1.1 C $Name: $
3    
4     #include "MNC_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8 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     I gname )
329    
330     implicit none
331     #include "mnc_common.h"
332     #include "EEPARAMS.h"
333    
334     C Arguments
335     integer myThid
336     character*(*) vname, gname
337    
338     C Functions
339     integer IFNBLNK, ILNBLNK
340    
341     C Local Variables
342     integer i, nvf,nvl, ngf,ngl, indv,indg
343     character*(MAX_LEN_MBUF) msgbuf
344    
345     nvf = IFNBLNK(vname)
346     nvl = ILNBLNK(vname)
347     ngf = IFNBLNK(gname)
348     ngl = ILNBLNK(gname)
349    
350     C Check that this vname is not already defined
351     CALL MNC_GET_IND(myThid, MNC_MAX_ID, vname, mnc_cw_vname, indv)
352     IF (indv .GT. 0) THEN
353     write(msgbuf,'(3a)') 'MNC_CW_ADD_VNAME ERROR: ''',
354     & vname(nvf:nvl), ''' is already defined'
355     CALL print_error(msgbuf, mythid)
356     stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
357     ENDIF
358     CALL MNC_GET_NEXT_EMPTY_IND(myThid, MNC_MAX_ID, mnc_cw_vname,
359     & indv)
360    
361     C Check that gname exists
362     CALL MNC_GET_IND(myThid, MNC_MAX_ID, gname, mnc_cw_gname, indg)
363     IF (indg .LT. 1) THEN
364     write(msgbuf,'(3a)') 'MNC_CW_ADD_VNAME ERROR: ''',
365     & gname(ngf:ngl), ''' is not defined'
366     CALL print_error(msgbuf, mythid)
367     stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
368     ENDIF
369    
370     mnc_cw_vname(indv)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
371     mnc_cw_vname(indv)(1:(nvl-nvf+1)) = vname(nvf:nvl)
372     mnc_cw_vgind(indv) = indg
373     DO i = 1,3
374     mnc_cw_vnat(i,indv) = 0
375     ENDDO
376    
377     RETURN
378     END
379    
380     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
381    
382 edhill 1.3 SUBROUTINE MNC_CW_ADD_VATTR_TEXT(
383     I myThid,
384     I vname,
385     I ntat,
386     I tnames,
387     I tvals )
388    
389     implicit none
390    
391     C Arguments
392     integer myThid, ntat
393     character*(*) vname, tnames(*), tvals(*)
394    
395     CALL MNC_CW_ADD_VATTR_ANY(myThid, vname,
396     & ntat, 0, 0,
397     & tnames, ' ', ' ',
398     & tvals, 0, 0.0D0 )
399    
400     RETURN
401     END
402    
403     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
404    
405     SUBROUTINE MNC_CW_ADD_VATTR_INT(
406     I myThid,
407     I vname,
408     I niat,
409     I inames,
410     I ivals )
411    
412     implicit none
413    
414     C Arguments
415     integer myThid, niat
416     character*(*) vname, inames(*)
417     integer ivals(*)
418    
419     CALL MNC_CW_ADD_VATTR_ANY(myThid, vname,
420     & 0, niat, 0,
421     & ' ', inames, ' ',
422     & ' ', ivals, 0.0D0 )
423    
424     RETURN
425     END
426    
427     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
428    
429     SUBROUTINE MNC_CW_ADD_VATTR_DBL(
430     I myThid,
431     I vname,
432     I ndat,
433     I dnames,
434     I dvals )
435    
436     implicit none
437    
438     C Arguments
439     integer myThid, ndat
440     character*(*) vname, dnames(*)
441     REAL*8 dvals(*)
442    
443     CALL MNC_CW_ADD_VATTR_ANY(myThid, vname,
444     & 0, 0, ndat,
445     & ' ', ' ', dnames,
446     & ' ', 0, dvals )
447    
448     RETURN
449     END
450    
451     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
452    
453 edhill 1.2 SUBROUTINE MNC_CW_ADD_VATTR_ANY(
454     I myThid,
455     I vname,
456     I ntat, niat, ndat,
457     I tnames, inames, dnames,
458     I tvals, ivals, dvals )
459    
460     implicit none
461     #include "mnc_common.h"
462     #include "EEPARAMS.h"
463    
464     C Arguments
465     integer myThid, ntat, niat, ndat
466     character*(*) vname
467     character*(*) tnames(*), inames(*), dnames(*)
468     character*(*) tvals(*)
469     integer ivals(*)
470     REAL*8 dvals(*)
471    
472     C Functions
473     integer IFNBLNK, ILNBLNK
474    
475     C Local Variables
476     integer i, n, nvf,nvl, n1,n2, indv
477     character*(MAX_LEN_MBUF) msgbuf
478    
479     nvf = IFNBLNK(vname)
480     nvl = ILNBLNK(vname)
481    
482     C Check that vname is defined
483     CALL MNC_GET_IND(myThid, MNC_MAX_ID, vname, mnc_cw_vname, indv)
484     IF (indv .LT. 1) THEN
485     write(msgbuf,'(3a)') 'MNC_CW_ADD_VATTR_ANY ERROR: ''',
486     & vname(nvf:nvl), ''' is not defined'
487     CALL print_error(msgbuf, mythid)
488     stop 'ABNORMAL END: S/R MNC_CW_ADD_VATTR_ANY'
489     ENDIF
490    
491     C Text Attributes
492     n = mnc_cw_vnat(1,indv)
493     DO i = 1,ntat
494     n1 = IFNBLNK(tnames(i))
495     n2 = ILNBLNK(tnames(i))
496     mnc_cw_vtnm(n+i,indv)(1:(n2-n1+1)) = tnames(i)(n1:n2)
497     n1 = IFNBLNK(tvals(i))
498     n2 = ILNBLNK(tvals(i))
499     mnc_cw_vtat(n+i,indv)(1:(n2-n1+1)) = tvals(i)(n1:n2)
500     ENDDO
501     mnc_cw_vnat(1,indv) = n + ntat
502    
503     C Integer Attributes
504     n = mnc_cw_vnat(2,indv)
505     DO i = 1,niat
506     n1 = IFNBLNK(inames(i))
507     n2 = ILNBLNK(inames(i))
508     mnc_cw_vinm(n+i,indv)(1:(n2-n1+1)) = inames(i)(n1:n2)
509     mnc_cw_viat(n+i,indv) = ivals(i)
510     ENDDO
511     mnc_cw_vnat(2,indv) = n + niat
512    
513     C Double Attributes
514     n = mnc_cw_vnat(3,indv)
515     DO i = 1,ndat
516     n1 = IFNBLNK(dnames(i))
517     n2 = ILNBLNK(dnames(i))
518     mnc_cw_vdnm(n+i,indv)(1:(n2-n1+1)) = dnames(i)(n1:n2)
519     mnc_cw_vdat(n+i,indv) = dvals(i)
520     ENDDO
521     mnc_cw_vnat(3,indv) = n + ndat
522 edhill 1.3
523     RETURN
524     END
525    
526     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
527    
528     SUBROUTINE MNC_CW_GET_TILE_NUM(
529     I myThid,
530     I bi, bj,
531     O uniq_tnum )
532    
533     implicit none
534     #include "EEPARAMS.h"
535     #include "SIZE.h"
536    
537     C Arguments
538     integer myThid, bi,bj, uniq_tnum
539    
540     C Local Variables
541     integer iG,jG
542    
543 edhill 1.4 iG = 0
544     jG = 0
545    
546 edhill 1.3 #ifdef ALLOW_EXCH2
547    
548     #include "W2_EXCH2_PARAMS.h"
549     uniq_tnum = W2_myTileList(bi)
550    
551     #else
552    
553     C Global tile number for simple (non-cube) domains
554     iG = bi+(myXGlobalLo-1)/sNx
555     jG = bj+(myYGlobalLo-1)/sNy
556 edhill 1.4
557     uniq_tnum = (jG - 1)*(nPx*nSx) + iG
558 edhill 1.3
559     #endif
560    
561 edhill 1.4 CEH3 write(*,*) 'iG,jG,uniq_tnum :', iG,jG,uniq_tnum
562    
563 edhill 1.3 RETURN
564     END
565    
566     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
567    
568     SUBROUTINE MNC_CW_FILE_AORC(
569     I myThid,
570 edhill 1.4 I fname,
571     O indf )
572 edhill 1.3
573     implicit none
574     #include "netcdf.inc"
575     #include "mnc_common.h"
576     #include "EEPARAMS.h"
577    
578     C Arguments
579 edhill 1.4 integer myThid, indf
580 edhill 1.3 character*(*) fname
581    
582     C Local Variables
583 edhill 1.4 integer i, ierr
584 edhill 1.3 character*(MAX_LEN_MBUF) msgbuf
585    
586     C Check if the file is already open
587     CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, indf)
588     IF (indf .GT. 0) THEN
589     RETURN
590     ENDIF
591    
592     C Try to open an existing file
593 edhill 1.4 CALL MNC_FILE_TRY_READ(myThid, fname, ierr, indf)
594 edhill 1.3 IF (ierr .EQ. NF_NOERR) THEN
595     RETURN
596     ENDIF
597    
598     C Try to create a new one
599 edhill 1.4 CALL MNC_FILE_OPEN(myThid, fname, 0, indf)
600 edhill 1.2
601 edhill 1.1 RETURN
602     END
603    
604     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
605    

  ViewVC Help
Powered by ViewVC 1.1.22